Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype RelName = RelName {}
- relNameToTxt :: RelName -> Text
- fromRemoteRelationship :: RelName -> FieldName
- data RelType
- relTypeToTxt :: RelType -> Text
- data JsonAggSelect
- data InsertOrder
- newtype OID = OID {}
- newtype FieldName = FieldName {}
- type Fields a = [(FieldName, a)]
- class ToAesonPairs a where
- toAesonPairs :: KeyValue v => a -> [v]
- data SourceName
- sourceNameToText :: SourceName -> Text
- defaultSource :: SourceName
- data InpValInfo = InpValInfo {}
- newtype SystemDefined = SystemDefined {}
- isSystemDefined :: SystemDefined -> Bool
- data SQLGenCtx = SQLGenCtx {}
- successMsg :: EncJSON
- failureMsg :: EncJSON
- newtype ResolvedWebhook = ResolvedWebhook {}
- newtype InputWebhook = InputWebhook {}
- newtype ResolveWebhookError = ResolveWebhookError {}
- resolveWebhook :: QErrM m => Environment -> InputWebhook -> m ResolvedWebhook
- resolveWebhookEither :: Environment -> InputWebhook -> Either ResolveWebhookError ResolvedWebhook
- newtype Timeout = Timeout {}
- defaultActionTimeoutSecs :: Timeout
- data PGConnectionParams = PGConnectionParams {
- _pgcpHost :: Text
- _pgcpUsername :: Text
- _pgcpPassword :: Maybe Text
- _pgcpPort :: Int
- _pgcpDatabase :: Text
- data UrlConf
- getConnOptionsFromConnParams :: PGConnectionParams -> ConnOptions
- getPGConnectionStringFromParams :: PGConnectionParams -> String
- resolveUrlConf :: MonadError QErr m => Environment -> UrlConf -> m Text
- getEnv :: QErrM m => Environment -> Text -> m Text
- getEnvEither :: Environment -> Text -> Either Text Text
- data MetricsConfig = MetricsConfig {}
- emptyMetricsConfig :: MetricsConfig
- data Comment
- commentToMaybeText :: Comment -> Maybe Text
- commentFromMaybeText :: Maybe Text -> Comment
- data EnvRecord a = EnvRecord {
- _envVarName :: Text
- _envVarValue :: a
- data ApolloFederationVersion = V1
- data ApolloFederationConfig = ApolloFederationConfig {}
- isApolloFedV1enabled :: Maybe ApolloFederationConfig -> Bool
- data TriggerOnReplication
- data RemoteRelationshipG definition = RemoteRelationship {
- _rrName :: RelName
- _rrDefinition :: definition
- rrName :: Lens (RemoteRelationshipG def) (RemoteRelationshipG def) RelName RelName
- rrDefinition :: Lens (RemoteRelationshipG def) (RemoteRelationshipG def') def def'
- remoteRelationshipCodec :: forall definition. Typeable definition => JSONCodec definition -> JSONCodec (RemoteRelationshipG definition)
Documentation
Instances
FromJSON RelName Source # | |
FromJSONKey RelName Source # | |
ToJSON RelName Source # | |
ToJSONKey RelName Source # | |
Defined in Hasura.RQL.Types.Common | |
HasCodec RelName Source # | |
Generic RelName Source # | |
Show RelName Source # | |
NFData RelName Source # | |
Defined in Hasura.RQL.Types.Common | |
Eq RelName Source # | |
Ord RelName Source # | |
IsIdentifier RelName Source # | |
Defined in Hasura.Backends.Postgres.SQL.Types toIdentifier :: RelName -> Identifier Source # | |
Hashable RelName Source # | |
ToTxt RelName Source # | |
FromCol RelName Source # | |
Defined in Hasura.RQL.Types.Common | |
ToPrepArg RelName Source # | |
type Rep RelName Source # | |
Defined in Hasura.RQL.Types.Common type Rep RelName = D1 ('MetaData "RelName" "Hasura.RQL.Types.Common" "graphql-engine-1.0.0-inplace" 'True) (C1 ('MetaCons "RelName" 'PrefixI 'True) (S1 ('MetaSel ('Just "getRelTxt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NonEmptyText))) |
relNameToTxt :: RelName -> Text Source #
Instances
FromJSON RelType Source # | |
ToJSON RelType Source # | |
HasCodec RelType Source # | |
Data RelType Source # | |
Defined in Hasura.RQL.Types.Common gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RelType -> c RelType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RelType # toConstr :: RelType -> Constr # dataTypeOf :: RelType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RelType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RelType) # gmapT :: (forall b. Data b => b -> b) -> RelType -> RelType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RelType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RelType -> r # gmapQ :: (forall d. Data d => d -> u) -> RelType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RelType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RelType -> m RelType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RelType -> m RelType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RelType -> m RelType # | |
Generic RelType Source # | |
Show RelType Source # | |
NFData RelType Source # | |
Defined in Hasura.RQL.Types.Common | |
Eq RelType Source # | |
Ord RelType Source # | |
Hashable RelType Source # | |
FromCol RelType Source # | |
Defined in Hasura.RQL.Types.Common | |
type Rep RelType Source # | |
relTypeToTxt :: RelType -> Text Source #
data JsonAggSelect Source #
Instances
data InsertOrder Source #
Instances
Postgres OIDs. https://www.postgresql.org/docs/12/datatype-oid.html
Instances
class ToAesonPairs a where Source #
toAesonPairs :: KeyValue v => a -> [v] Source #
Instances
ToJSON a => ToAesonPairs (RelDef a) Source # | |
Defined in Hasura.RQL.Types.Relationships.Local toAesonPairs :: KeyValue v => RelDef a -> [v] Source # | |
Backend b => ToAesonPairs (PermDef b perm) Source # | |
Defined in Hasura.RQL.Types.Permission toAesonPairs :: KeyValue v => PermDef b perm -> [v] Source # |
data SourceName Source #
Instances
sourceNameToText :: SourceName -> Text Source #
data InpValInfo Source #
Instances
newtype SystemDefined Source #
Instances
isSystemDefined :: SystemDefined -> Bool Source #
successMsg :: EncJSON Source #
failureMsg :: EncJSON Source #
newtype ResolvedWebhook Source #
Instances
newtype InputWebhook Source #
Instances
newtype ResolveWebhookError Source #
Instances
Show ResolveWebhookError Source # | |
Defined in Hasura.RQL.Types.Common showsPrec :: Int -> ResolveWebhookError -> ShowS # show :: ResolveWebhookError -> String # showList :: [ResolveWebhookError] -> ShowS # | |
ToTxt ResolveWebhookError Source # | |
Defined in Hasura.RQL.Types.Common toTxt :: ResolveWebhookError -> Text Source # |
resolveWebhook :: QErrM m => Environment -> InputWebhook -> m ResolvedWebhook Source #
resolveWebhookEither :: Environment -> InputWebhook -> Either ResolveWebhookError ResolvedWebhook Source #
data PGConnectionParams Source #
See API reference here: https://hasura.io/docs/latest/graphql/core/api-reference/syntax-defs.html#pgconnectionparameters
PGConnectionParams | |
|
Instances
UrlValue InputWebhook | the database connection string |
UrlFromEnv Text | the name of environment variable containing the connection string |
UrlFromParams PGConnectionParams | the minimum required `connection parameters` to construct a valid connection string |
Instances
FromJSON UrlConf Source # | |
ToJSON UrlConf Source # | |
HasCodec UrlConf Source # | |
Generic UrlConf Source # | |
Show UrlConf Source # | |
NFData UrlConf Source # | |
Defined in Hasura.RQL.Types.Common | |
Eq UrlConf Source # | |
Hashable UrlConf Source # | |
type Rep UrlConf Source # | |
Defined in Hasura.RQL.Types.Common type Rep UrlConf = D1 ('MetaData "UrlConf" "Hasura.RQL.Types.Common" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "UrlValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 InputWebhook)) :+: (C1 ('MetaCons "UrlFromEnv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "UrlFromParams" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PGConnectionParams)))) |
getPGConnectionStringFromParams :: PGConnectionParams -> String Source #
Construct a Postgres connection URI as a String from PGConnectionParams
.
NOTE: This function takes care to properly escape all URI components, as Postgres requires that a connection URI is percent-encoded if it includes symbols with "special meaning".
See the libpq
documentation for details: https://www.postgresql.org/docs/13/libpq-connect.html#id-1.7.3.8.3.6
resolveUrlConf :: MonadError QErr m => Environment -> UrlConf -> m Text Source #
getEnvEither :: Environment -> Text -> Either Text Text Source #
data MetricsConfig Source #
Various user-controlled configuration for metrics used by Pro
MetricsConfig | |
|
Instances
Automatic | Automatically generate a comment (derive it from DB comments, or a sensible default describing the source of the data) |
Explicit (Maybe NonEmptyText) | The user's explicitly provided comment, or explicitly no comment (ie. leave it blank, do not autogenerate one) |
Instances
FromJSON Comment Source # | |
ToJSON Comment Source # | |
HasCodec Comment Source # | |
Generic Comment Source # | |
Show Comment Source # | |
NFData Comment Source # | |
Defined in Hasura.RQL.Types.Common | |
Eq Comment Source # | |
Hashable Comment Source # | |
type Rep Comment Source # | |
Defined in Hasura.RQL.Types.Common type Rep Comment = D1 ('MetaData "Comment" "Hasura.RQL.Types.Common" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "Automatic" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Explicit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe NonEmptyText)))) |
We use the following type, after we resolve the env var. | This will store both the env var name and the resolved value.
EnvRecord | |
|
Instances
FromJSON a => FromJSON (EnvRecord a) Source # | |
ToJSON a => ToJSON (EnvRecord a) Source # | |
Generic (EnvRecord a) Source # | |
Show a => Show (EnvRecord a) Source # | |
NFData a => NFData (EnvRecord a) Source # | |
Defined in Hasura.RQL.Types.Common | |
Eq a => Eq (EnvRecord a) Source # | |
Hashable a => Hashable (EnvRecord a) Source # | |
type Rep (EnvRecord a) Source # | |
Defined in Hasura.RQL.Types.Common type Rep (EnvRecord a) = D1 ('MetaData "EnvRecord" "Hasura.RQL.Types.Common" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "EnvRecord" 'PrefixI 'True) (S1 ('MetaSel ('Just "_envVarName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "_envVarValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a))) |
data ApolloFederationVersion Source #
Instances
FromJSON ApolloFederationVersion Source # | |
Defined in Hasura.RQL.Types.Common | |
ToJSON ApolloFederationVersion Source # | |
Defined in Hasura.RQL.Types.Common | |
HasCodec ApolloFederationVersion Source # | |
Generic ApolloFederationVersion Source # | |
Defined in Hasura.RQL.Types.Common type Rep ApolloFederationVersion :: Type -> Type # | |
Show ApolloFederationVersion Source # | |
Defined in Hasura.RQL.Types.Common showsPrec :: Int -> ApolloFederationVersion -> ShowS # show :: ApolloFederationVersion -> String # showList :: [ApolloFederationVersion] -> ShowS # | |
NFData ApolloFederationVersion Source # | |
Defined in Hasura.RQL.Types.Common rnf :: ApolloFederationVersion -> () # | |
Eq ApolloFederationVersion Source # | |
Defined in Hasura.RQL.Types.Common | |
type Rep ApolloFederationVersion Source # | |
data ApolloFederationConfig Source #
Instances
data TriggerOnReplication Source #
Type to indicate if the SQL trigger should be enabled when data is inserted into a table through replication.
Instances
data RemoteRelationshipG definition Source #
Metadata representation of a generic remote relationship, regardless of the source: all sources use this same agnostic definition. The internal definition field is where we differentiate between different targets.
TODO: This needs to be moved to an appropriate module, maybe something like Hasura.RemoteRelationships.Metadata.
RemoteRelationship | |
|
Instances
rrName :: Lens (RemoteRelationshipG def) (RemoteRelationshipG def) RelName RelName Source #
rrDefinition :: Lens (RemoteRelationshipG def) (RemoteRelationshipG def') def def' Source #
remoteRelationshipCodec :: forall definition. Typeable definition => JSONCodec definition -> JSONCodec (RemoteRelationshipG definition) Source #