{-# LANGUAGE TemplateHaskell #-}
module Hasura.Backends.Postgres.SQL.Types
( pgFmtLit,
pgFmtIdentifier,
isView,
QualifiedTable,
QualifiedFunction,
PGDescription (..),
PGCol,
unsafePGCol,
getPGColTxt,
showPGCols,
isNumType,
stringTypes,
isStringType,
isJSONType,
isComparableType,
isBigNum,
geoTypes,
isGeoType,
IsIdentifier (..),
Identifier (..),
SchemaName (..),
publicSchema,
hdbCatalogSchema,
TableName (..),
FunctionName (..),
ConstraintName (..),
QualifiedObject (..),
getIdentifierQualifiedObject,
qualifiedObjectToText,
snakeCaseQualifiedObject,
namingConventionSupport,
qualifiedObjectToName,
PGScalarType (..),
textToPGScalarType,
pgScalarTranslations,
pgScalarTypeToText,
PGTypeKind (..),
QualifiedPGType (..),
isBaseType,
typeToTable,
mkFunctionArgScalarType,
PGRawFunctionInfo (..),
mkScalarTypeName,
pgTypeOid,
)
where
import Data.Aeson
import Data.Aeson.Encoding (text)
import Data.Aeson.Key qualified as K
import Data.Aeson.TH
import Data.Aeson.Types (toJSONKeyText)
import Data.Int
import Data.List (uncons)
import Data.Text qualified as T
import Data.Text.Casing qualified as C
import Data.Text.Extended
import Database.PG.Query qualified as Q
import Database.PG.Query.PTI qualified as PTI
import Database.PostgreSQL.LibPQ qualified as PQ
import Hasura.Base.Error
import Hasura.Base.ErrorValue qualified as ErrorValue
import Hasura.Base.ToErrorValue
import Hasura.GraphQL.Parser.Name qualified as GName
import Hasura.Incremental (Cacheable)
import Hasura.Name qualified as Name
import Hasura.Prelude
import Hasura.RQL.Types.Backend (SupportedNamingCase (..))
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.Function
import Hasura.SQL.Types
import Language.GraphQL.Draft.Syntax qualified as G
import PostgreSQL.Binary.Decoding qualified as PD
import Text.Builder qualified as TB
newtype Identifier = Identifier {Identifier -> Text
getIdenTxt :: Text}
deriving (Int -> Identifier -> ShowS
[Identifier] -> ShowS
Identifier -> String
(Int -> Identifier -> ShowS)
-> (Identifier -> String)
-> ([Identifier] -> ShowS)
-> Show Identifier
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Identifier] -> ShowS
$cshowList :: [Identifier] -> ShowS
show :: Identifier -> String
$cshow :: Identifier -> String
showsPrec :: Int -> Identifier -> ShowS
$cshowsPrec :: Int -> Identifier -> ShowS
Show, Identifier -> Identifier -> Bool
(Identifier -> Identifier -> Bool)
-> (Identifier -> Identifier -> Bool) -> Eq Identifier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identifier -> Identifier -> Bool
$c/= :: Identifier -> Identifier -> Bool
== :: Identifier -> Identifier -> Bool
$c== :: Identifier -> Identifier -> Bool
Eq, Identifier -> ()
(Identifier -> ()) -> NFData Identifier
forall a. (a -> ()) -> NFData a
rnf :: Identifier -> ()
$crnf :: Identifier -> ()
NFData, Value -> Parser [Identifier]
Value -> Parser Identifier
(Value -> Parser Identifier)
-> (Value -> Parser [Identifier]) -> FromJSON Identifier
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Identifier]
$cparseJSONList :: Value -> Parser [Identifier]
parseJSON :: Value -> Parser Identifier
$cparseJSON :: Value -> Parser Identifier
FromJSON, [Identifier] -> Value
[Identifier] -> Encoding
Identifier -> Value
Identifier -> Encoding
(Identifier -> Value)
-> (Identifier -> Encoding)
-> ([Identifier] -> Value)
-> ([Identifier] -> Encoding)
-> ToJSON Identifier
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Identifier] -> Encoding
$ctoEncodingList :: [Identifier] -> Encoding
toJSONList :: [Identifier] -> Value
$ctoJSONList :: [Identifier] -> Value
toEncoding :: Identifier -> Encoding
$ctoEncoding :: Identifier -> Encoding
toJSON :: Identifier -> Value
$ctoJSON :: Identifier -> Value
ToJSON, Int -> Identifier -> Int
Identifier -> Int
(Int -> Identifier -> Int)
-> (Identifier -> Int) -> Hashable Identifier
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Identifier -> Int
$chash :: Identifier -> Int
hashWithSalt :: Int -> Identifier -> Int
$chashWithSalt :: Int -> Identifier -> Int
Hashable, b -> Identifier -> Identifier
NonEmpty Identifier -> Identifier
Identifier -> Identifier -> Identifier
(Identifier -> Identifier -> Identifier)
-> (NonEmpty Identifier -> Identifier)
-> (forall b. Integral b => b -> Identifier -> Identifier)
-> Semigroup Identifier
forall b. Integral b => b -> Identifier -> Identifier
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> Identifier -> Identifier
$cstimes :: forall b. Integral b => b -> Identifier -> Identifier
sconcat :: NonEmpty Identifier -> Identifier
$csconcat :: NonEmpty Identifier -> Identifier
<> :: Identifier -> Identifier -> Identifier
$c<> :: Identifier -> Identifier -> Identifier
Semigroup, Typeable Identifier
DataType
Constr
Typeable Identifier
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Identifier -> c Identifier)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Identifier)
-> (Identifier -> Constr)
-> (Identifier -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Identifier))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Identifier))
-> ((forall b. Data b => b -> b) -> Identifier -> Identifier)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Identifier -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Identifier -> r)
-> (forall u. (forall d. Data d => d -> u) -> Identifier -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Identifier -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Identifier -> m Identifier)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Identifier -> m Identifier)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Identifier -> m Identifier)
-> Data Identifier
Identifier -> DataType
Identifier -> Constr
(forall b. Data b => b -> b) -> Identifier -> Identifier
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Identifier -> c Identifier
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Identifier
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Identifier -> u
forall u. (forall d. Data d => d -> u) -> Identifier -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Identifier -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Identifier -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Identifier -> m Identifier
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Identifier -> m Identifier
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Identifier
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Identifier -> c Identifier
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Identifier)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Identifier)
$cIdentifier :: Constr
$tIdentifier :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Identifier -> m Identifier
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Identifier -> m Identifier
gmapMp :: (forall d. Data d => d -> m d) -> Identifier -> m Identifier
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Identifier -> m Identifier
gmapM :: (forall d. Data d => d -> m d) -> Identifier -> m Identifier
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Identifier -> m Identifier
gmapQi :: Int -> (forall d. Data d => d -> u) -> Identifier -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Identifier -> u
gmapQ :: (forall d. Data d => d -> u) -> Identifier -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Identifier -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Identifier -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Identifier -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Identifier -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Identifier -> r
gmapT :: (forall b. Data b => b -> b) -> Identifier -> Identifier
$cgmapT :: (forall b. Data b => b -> b) -> Identifier -> Identifier
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Identifier)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Identifier)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Identifier)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Identifier)
dataTypeOf :: Identifier -> DataType
$cdataTypeOf :: Identifier -> DataType
toConstr :: Identifier -> Constr
$ctoConstr :: Identifier -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Identifier
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Identifier
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Identifier -> c Identifier
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Identifier -> c Identifier
$cp1Data :: Typeable Identifier
Data, Eq Identifier
Eq Identifier
-> (Accesses -> Identifier -> Identifier -> Bool)
-> Cacheable Identifier
Accesses -> Identifier -> Identifier -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> Identifier -> Identifier -> Bool
$cunchanged :: Accesses -> Identifier -> Identifier -> Bool
$cp1Cacheable :: Eq Identifier
Cacheable)
instance ToSQL Identifier where
toSQL :: Identifier -> Builder
toSQL (Identifier Text
t) =
Text -> Builder
TB.text (Text -> Builder) -> Text -> Builder
forall a b. (a -> b) -> a -> b
$ Text -> Text
pgFmtIdentifier Text
t
class IsIdentifier a where
toIdentifier :: a -> Identifier
instance IsIdentifier Identifier where
toIdentifier :: Identifier -> Identifier
toIdentifier = Identifier -> Identifier
forall a. a -> a
id
pgFmtIdentifier :: Text -> Text
pgFmtIdentifier :: Text -> Text
pgFmtIdentifier Text
x =
Text
"\"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text -> Text -> Text
T.replace Text
"\"" Text
"\"\"" (Text -> Text
trimNullChars Text
x) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\""
pgFmtLit :: Text -> Text
pgFmtLit :: Text -> Text
pgFmtLit Text
x =
let trimmed :: Text
trimmed = Text -> Text
trimNullChars Text
x
escaped :: Text
escaped = Text
"'" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text -> Text -> Text
T.replace Text
"'" Text
"''" Text
trimmed Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"'"
slashed :: Text
slashed = Text -> Text -> Text -> Text
T.replace Text
"\\" Text
"\\\\" Text
escaped
in if Text
"\\" Text -> Text -> Bool
`T.isInfixOf` Text
escaped
then Text
"E" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
slashed
else Text
slashed
trimNullChars :: Text -> Text
trimNullChars :: Text -> Text
trimNullChars = (Char -> Bool) -> Text -> Text
T.takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\x0')
newtype TableName = TableName {TableName -> Text
getTableTxt :: Text}
deriving
( Int -> TableName -> ShowS
[TableName] -> ShowS
TableName -> String
(Int -> TableName -> ShowS)
-> (TableName -> String)
-> ([TableName] -> ShowS)
-> Show TableName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TableName] -> ShowS
$cshowList :: [TableName] -> ShowS
show :: TableName -> String
$cshow :: TableName -> String
showsPrec :: Int -> TableName -> ShowS
$cshowsPrec :: Int -> TableName -> ShowS
Show,
TableName -> TableName -> Bool
(TableName -> TableName -> Bool)
-> (TableName -> TableName -> Bool) -> Eq TableName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TableName -> TableName -> Bool
$c/= :: TableName -> TableName -> Bool
== :: TableName -> TableName -> Bool
$c== :: TableName -> TableName -> Bool
Eq,
Eq TableName
Eq TableName
-> (TableName -> TableName -> Ordering)
-> (TableName -> TableName -> Bool)
-> (TableName -> TableName -> Bool)
-> (TableName -> TableName -> Bool)
-> (TableName -> TableName -> Bool)
-> (TableName -> TableName -> TableName)
-> (TableName -> TableName -> TableName)
-> Ord TableName
TableName -> TableName -> Bool
TableName -> TableName -> Ordering
TableName -> TableName -> TableName
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 :: TableName -> TableName -> TableName
$cmin :: TableName -> TableName -> TableName
max :: TableName -> TableName -> TableName
$cmax :: TableName -> TableName -> TableName
>= :: TableName -> TableName -> Bool
$c>= :: TableName -> TableName -> Bool
> :: TableName -> TableName -> Bool
$c> :: TableName -> TableName -> Bool
<= :: TableName -> TableName -> Bool
$c<= :: TableName -> TableName -> Bool
< :: TableName -> TableName -> Bool
$c< :: TableName -> TableName -> Bool
compare :: TableName -> TableName -> Ordering
$ccompare :: TableName -> TableName -> Ordering
$cp1Ord :: Eq TableName
Ord,
Value -> Parser [TableName]
Value -> Parser TableName
(Value -> Parser TableName)
-> (Value -> Parser [TableName]) -> FromJSON TableName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TableName]
$cparseJSONList :: Value -> Parser [TableName]
parseJSON :: Value -> Parser TableName
$cparseJSON :: Value -> Parser TableName
FromJSON,
[TableName] -> Value
[TableName] -> Encoding
TableName -> Value
TableName -> Encoding
(TableName -> Value)
-> (TableName -> Encoding)
-> ([TableName] -> Value)
-> ([TableName] -> Encoding)
-> ToJSON TableName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TableName] -> Encoding
$ctoEncodingList :: [TableName] -> Encoding
toJSONList :: [TableName] -> Value
$ctoJSONList :: [TableName] -> Value
toEncoding :: TableName -> Encoding
$ctoEncoding :: TableName -> Encoding
toJSON :: TableName -> Value
$ctoJSON :: TableName -> Value
ToJSON,
Int -> TableName -> Int
TableName -> Int
(Int -> TableName -> Int)
-> (TableName -> Int) -> Hashable TableName
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: TableName -> Int
$chash :: TableName -> Int
hashWithSalt :: Int -> TableName -> Int
$chashWithSalt :: Int -> TableName -> Int
Hashable,
TableName -> PrepArg
(TableName -> PrepArg) -> ToPrepArg TableName
forall a. (a -> PrepArg) -> ToPrepArg a
toPrepVal :: TableName -> PrepArg
$ctoPrepVal :: TableName -> PrepArg
Q.ToPrepArg,
Maybe ByteString -> Either Text TableName
(Maybe ByteString -> Either Text TableName) -> FromCol TableName
forall a. (Maybe ByteString -> Either Text a) -> FromCol a
fromCol :: Maybe ByteString -> Either Text TableName
$cfromCol :: Maybe ByteString -> Either Text TableName
Q.FromCol,
Typeable TableName
DataType
Constr
Typeable TableName
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TableName -> c TableName)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TableName)
-> (TableName -> Constr)
-> (TableName -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TableName))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableName))
-> ((forall b. Data b => b -> b) -> TableName -> TableName)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TableName -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TableName -> r)
-> (forall u. (forall d. Data d => d -> u) -> TableName -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> TableName -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TableName -> m TableName)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableName -> m TableName)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableName -> m TableName)
-> Data TableName
TableName -> DataType
TableName -> Constr
(forall b. Data b => b -> b) -> TableName -> TableName
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TableName -> c TableName
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TableName
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> TableName -> u
forall u. (forall d. Data d => d -> u) -> TableName -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TableName -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TableName -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TableName -> m TableName
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableName -> m TableName
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TableName
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TableName -> c TableName
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TableName)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableName)
$cTableName :: Constr
$tTableName :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> TableName -> m TableName
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableName -> m TableName
gmapMp :: (forall d. Data d => d -> m d) -> TableName -> m TableName
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableName -> m TableName
gmapM :: (forall d. Data d => d -> m d) -> TableName -> m TableName
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TableName -> m TableName
gmapQi :: Int -> (forall d. Data d => d -> u) -> TableName -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TableName -> u
gmapQ :: (forall d. Data d => d -> u) -> TableName -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TableName -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TableName -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TableName -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TableName -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TableName -> r
gmapT :: (forall b. Data b => b -> b) -> TableName -> TableName
$cgmapT :: (forall b. Data b => b -> b) -> TableName -> TableName
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableName)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableName)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c TableName)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TableName)
dataTypeOf :: TableName -> DataType
$cdataTypeOf :: TableName -> DataType
toConstr :: TableName -> Constr
$ctoConstr :: TableName -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TableName
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TableName
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TableName -> c TableName
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TableName -> c TableName
$cp1Data :: Typeable TableName
Data,
(forall x. TableName -> Rep TableName x)
-> (forall x. Rep TableName x -> TableName) -> Generic TableName
forall x. Rep TableName x -> TableName
forall x. TableName -> Rep TableName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TableName x -> TableName
$cfrom :: forall x. TableName -> Rep TableName x
Generic,
TableName -> ()
(TableName -> ()) -> NFData TableName
forall a. (a -> ()) -> NFData a
rnf :: TableName -> ()
$crnf :: TableName -> ()
NFData,
Eq TableName
Eq TableName
-> (Accesses -> TableName -> TableName -> Bool)
-> Cacheable TableName
Accesses -> TableName -> TableName -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> TableName -> TableName -> Bool
$cunchanged :: Accesses -> TableName -> TableName -> Bool
$cp1Cacheable :: Eq TableName
Cacheable,
String -> TableName
(String -> TableName) -> IsString TableName
forall a. (String -> a) -> IsString a
fromString :: String -> TableName
$cfromString :: String -> TableName
IsString
)
instance IsIdentifier TableName where
toIdentifier :: TableName -> Identifier
toIdentifier (TableName Text
t) = Text -> Identifier
Identifier Text
t
instance ToTxt TableName where
toTxt :: TableName -> Text
toTxt (TableName Text
t) = Text
t
instance ToSQL TableName where
toSQL :: TableName -> Builder
toSQL = Identifier -> Builder
forall a. ToSQL a => a -> Builder
toSQL (Identifier -> Builder)
-> (TableName -> Identifier) -> TableName -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableName -> Identifier
forall a. IsIdentifier a => a -> Identifier
toIdentifier
data TableType
= TTBaseTable
| TTView
| TTForeignTable
| TTLocalTemporary
deriving (TableType -> TableType -> Bool
(TableType -> TableType -> Bool)
-> (TableType -> TableType -> Bool) -> Eq TableType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TableType -> TableType -> Bool
$c/= :: TableType -> TableType -> Bool
== :: TableType -> TableType -> Bool
$c== :: TableType -> TableType -> Bool
Eq)
instance Q.FromCol TableType where
fromCol :: Maybe ByteString -> Either Text TableType
fromCol Maybe ByteString
bs = (Value TableType -> Maybe ByteString -> Either Text TableType)
-> Maybe ByteString -> Value TableType -> Either Text TableType
forall a b c. (a -> b -> c) -> b -> a -> c
flip Value TableType -> Maybe ByteString -> Either Text TableType
forall a. Value a -> Maybe ByteString -> Either Text a
Q.fromColHelper Maybe ByteString
bs (Value TableType -> Either Text TableType)
-> Value TableType -> Either Text TableType
forall a b. (a -> b) -> a -> b
$
(Text -> Maybe TableType) -> Value TableType
forall a. (Text -> Maybe a) -> Value a
PD.enum ((Text -> Maybe TableType) -> Value TableType)
-> (Text -> Maybe TableType) -> Value TableType
forall a b. (a -> b) -> a -> b
$ \case
Text
"BASE TABLE" -> TableType -> Maybe TableType
forall a. a -> Maybe a
Just TableType
TTBaseTable
Text
"VIEW" -> TableType -> Maybe TableType
forall a. a -> Maybe a
Just TableType
TTView
Text
"FOREIGN TABLE" -> TableType -> Maybe TableType
forall a. a -> Maybe a
Just TableType
TTForeignTable
Text
"LOCAL TEMPORARY" -> TableType -> Maybe TableType
forall a. a -> Maybe a
Just TableType
TTLocalTemporary
Text
_ -> Maybe TableType
forall a. Maybe a
Nothing
isView :: TableType -> Bool
isView :: TableType -> Bool
isView TableType
TTView = Bool
True
isView TableType
_ = Bool
False
newtype ConstraintName = ConstraintName {ConstraintName -> Text
getConstraintTxt :: Text}
deriving (Int -> ConstraintName -> ShowS
[ConstraintName] -> ShowS
ConstraintName -> String
(Int -> ConstraintName -> ShowS)
-> (ConstraintName -> String)
-> ([ConstraintName] -> ShowS)
-> Show ConstraintName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConstraintName] -> ShowS
$cshowList :: [ConstraintName] -> ShowS
show :: ConstraintName -> String
$cshow :: ConstraintName -> String
showsPrec :: Int -> ConstraintName -> ShowS
$cshowsPrec :: Int -> ConstraintName -> ShowS
Show, ConstraintName -> ConstraintName -> Bool
(ConstraintName -> ConstraintName -> Bool)
-> (ConstraintName -> ConstraintName -> Bool) -> Eq ConstraintName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConstraintName -> ConstraintName -> Bool
$c/= :: ConstraintName -> ConstraintName -> Bool
== :: ConstraintName -> ConstraintName -> Bool
$c== :: ConstraintName -> ConstraintName -> Bool
Eq, ConstraintName -> Text
(ConstraintName -> Text) -> ToTxt ConstraintName
forall a. (a -> Text) -> ToTxt a
toTxt :: ConstraintName -> Text
$ctoTxt :: ConstraintName -> Text
ToTxt, Value -> Parser [ConstraintName]
Value -> Parser ConstraintName
(Value -> Parser ConstraintName)
-> (Value -> Parser [ConstraintName]) -> FromJSON ConstraintName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ConstraintName]
$cparseJSONList :: Value -> Parser [ConstraintName]
parseJSON :: Value -> Parser ConstraintName
$cparseJSON :: Value -> Parser ConstraintName
FromJSON, [ConstraintName] -> Value
[ConstraintName] -> Encoding
ConstraintName -> Value
ConstraintName -> Encoding
(ConstraintName -> Value)
-> (ConstraintName -> Encoding)
-> ([ConstraintName] -> Value)
-> ([ConstraintName] -> Encoding)
-> ToJSON ConstraintName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ConstraintName] -> Encoding
$ctoEncodingList :: [ConstraintName] -> Encoding
toJSONList :: [ConstraintName] -> Value
$ctoJSONList :: [ConstraintName] -> Value
toEncoding :: ConstraintName -> Encoding
$ctoEncoding :: ConstraintName -> Encoding
toJSON :: ConstraintName -> Value
$ctoJSON :: ConstraintName -> Value
ToJSON, ConstraintName -> PrepArg
(ConstraintName -> PrepArg) -> ToPrepArg ConstraintName
forall a. (a -> PrepArg) -> ToPrepArg a
toPrepVal :: ConstraintName -> PrepArg
$ctoPrepVal :: ConstraintName -> PrepArg
Q.ToPrepArg, Maybe ByteString -> Either Text ConstraintName
(Maybe ByteString -> Either Text ConstraintName)
-> FromCol ConstraintName
forall a. (Maybe ByteString -> Either Text a) -> FromCol a
fromCol :: Maybe ByteString -> Either Text ConstraintName
$cfromCol :: Maybe ByteString -> Either Text ConstraintName
Q.FromCol, Int -> ConstraintName -> Int
ConstraintName -> Int
(Int -> ConstraintName -> Int)
-> (ConstraintName -> Int) -> Hashable ConstraintName
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ConstraintName -> Int
$chash :: ConstraintName -> Int
hashWithSalt :: Int -> ConstraintName -> Int
$chashWithSalt :: Int -> ConstraintName -> Int
Hashable, ConstraintName -> ()
(ConstraintName -> ()) -> NFData ConstraintName
forall a. (a -> ()) -> NFData a
rnf :: ConstraintName -> ()
$crnf :: ConstraintName -> ()
NFData, Eq ConstraintName
Eq ConstraintName
-> (Accesses -> ConstraintName -> ConstraintName -> Bool)
-> Cacheable ConstraintName
Accesses -> ConstraintName -> ConstraintName -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> ConstraintName -> ConstraintName -> Bool
$cunchanged :: Accesses -> ConstraintName -> ConstraintName -> Bool
$cp1Cacheable :: Eq ConstraintName
Cacheable)
instance IsIdentifier ConstraintName where
toIdentifier :: ConstraintName -> Identifier
toIdentifier (ConstraintName Text
t) = Text -> Identifier
Identifier Text
t
instance ToSQL ConstraintName where
toSQL :: ConstraintName -> Builder
toSQL = Identifier -> Builder
forall a. ToSQL a => a -> Builder
toSQL (Identifier -> Builder)
-> (ConstraintName -> Identifier) -> ConstraintName -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstraintName -> Identifier
forall a. IsIdentifier a => a -> Identifier
toIdentifier
instance ToErrorValue ConstraintName where
toErrorValue :: ConstraintName -> ErrorMessage
toErrorValue = Text -> ErrorMessage
ErrorValue.squote (Text -> ErrorMessage)
-> (ConstraintName -> Text) -> ConstraintName -> ErrorMessage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstraintName -> Text
getConstraintTxt
newtype FunctionName = FunctionName {FunctionName -> Text
getFunctionTxt :: Text}
deriving (Int -> FunctionName -> ShowS
[FunctionName] -> ShowS
FunctionName -> String
(Int -> FunctionName -> ShowS)
-> (FunctionName -> String)
-> ([FunctionName] -> ShowS)
-> Show FunctionName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FunctionName] -> ShowS
$cshowList :: [FunctionName] -> ShowS
show :: FunctionName -> String
$cshow :: FunctionName -> String
showsPrec :: Int -> FunctionName -> ShowS
$cshowsPrec :: Int -> FunctionName -> ShowS
Show, FunctionName -> FunctionName -> Bool
(FunctionName -> FunctionName -> Bool)
-> (FunctionName -> FunctionName -> Bool) -> Eq FunctionName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FunctionName -> FunctionName -> Bool
$c/= :: FunctionName -> FunctionName -> Bool
== :: FunctionName -> FunctionName -> Bool
$c== :: FunctionName -> FunctionName -> Bool
Eq, Eq FunctionName
Eq FunctionName
-> (FunctionName -> FunctionName -> Ordering)
-> (FunctionName -> FunctionName -> Bool)
-> (FunctionName -> FunctionName -> Bool)
-> (FunctionName -> FunctionName -> Bool)
-> (FunctionName -> FunctionName -> Bool)
-> (FunctionName -> FunctionName -> FunctionName)
-> (FunctionName -> FunctionName -> FunctionName)
-> Ord FunctionName
FunctionName -> FunctionName -> Bool
FunctionName -> FunctionName -> Ordering
FunctionName -> FunctionName -> FunctionName
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 :: FunctionName -> FunctionName -> FunctionName
$cmin :: FunctionName -> FunctionName -> FunctionName
max :: FunctionName -> FunctionName -> FunctionName
$cmax :: FunctionName -> FunctionName -> FunctionName
>= :: FunctionName -> FunctionName -> Bool
$c>= :: FunctionName -> FunctionName -> Bool
> :: FunctionName -> FunctionName -> Bool
$c> :: FunctionName -> FunctionName -> Bool
<= :: FunctionName -> FunctionName -> Bool
$c<= :: FunctionName -> FunctionName -> Bool
< :: FunctionName -> FunctionName -> Bool
$c< :: FunctionName -> FunctionName -> Bool
compare :: FunctionName -> FunctionName -> Ordering
$ccompare :: FunctionName -> FunctionName -> Ordering
$cp1Ord :: Eq FunctionName
Ord, Value -> Parser [FunctionName]
Value -> Parser FunctionName
(Value -> Parser FunctionName)
-> (Value -> Parser [FunctionName]) -> FromJSON FunctionName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [FunctionName]
$cparseJSONList :: Value -> Parser [FunctionName]
parseJSON :: Value -> Parser FunctionName
$cparseJSON :: Value -> Parser FunctionName
FromJSON, [FunctionName] -> Value
[FunctionName] -> Encoding
FunctionName -> Value
FunctionName -> Encoding
(FunctionName -> Value)
-> (FunctionName -> Encoding)
-> ([FunctionName] -> Value)
-> ([FunctionName] -> Encoding)
-> ToJSON FunctionName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [FunctionName] -> Encoding
$ctoEncodingList :: [FunctionName] -> Encoding
toJSONList :: [FunctionName] -> Value
$ctoJSONList :: [FunctionName] -> Value
toEncoding :: FunctionName -> Encoding
$ctoEncoding :: FunctionName -> Encoding
toJSON :: FunctionName -> Value
$ctoJSON :: FunctionName -> Value
ToJSON, FunctionName -> PrepArg
(FunctionName -> PrepArg) -> ToPrepArg FunctionName
forall a. (a -> PrepArg) -> ToPrepArg a
toPrepVal :: FunctionName -> PrepArg
$ctoPrepVal :: FunctionName -> PrepArg
Q.ToPrepArg, Maybe ByteString -> Either Text FunctionName
(Maybe ByteString -> Either Text FunctionName)
-> FromCol FunctionName
forall a. (Maybe ByteString -> Either Text a) -> FromCol a
fromCol :: Maybe ByteString -> Either Text FunctionName
$cfromCol :: Maybe ByteString -> Either Text FunctionName
Q.FromCol, Int -> FunctionName -> Int
FunctionName -> Int
(Int -> FunctionName -> Int)
-> (FunctionName -> Int) -> Hashable FunctionName
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: FunctionName -> Int
$chash :: FunctionName -> Int
hashWithSalt :: Int -> FunctionName -> Int
$chashWithSalt :: Int -> FunctionName -> Int
Hashable, Typeable FunctionName
DataType
Constr
Typeable FunctionName
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunctionName -> c FunctionName)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunctionName)
-> (FunctionName -> Constr)
-> (FunctionName -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunctionName))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FunctionName))
-> ((forall b. Data b => b -> b) -> FunctionName -> FunctionName)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionName -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionName -> r)
-> (forall u. (forall d. Data d => d -> u) -> FunctionName -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> FunctionName -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName)
-> Data FunctionName
FunctionName -> DataType
FunctionName -> Constr
(forall b. Data b => b -> b) -> FunctionName -> FunctionName
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunctionName -> c FunctionName
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunctionName
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> FunctionName -> u
forall u. (forall d. Data d => d -> u) -> FunctionName -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionName -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionName -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunctionName
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunctionName -> c FunctionName
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunctionName)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FunctionName)
$cFunctionName :: Constr
$tFunctionName :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> FunctionName -> m FunctionName
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName
gmapMp :: (forall d. Data d => d -> m d) -> FunctionName -> m FunctionName
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName
gmapM :: (forall d. Data d => d -> m d) -> FunctionName -> m FunctionName
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName
gmapQi :: Int -> (forall d. Data d => d -> u) -> FunctionName -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FunctionName -> u
gmapQ :: (forall d. Data d => d -> u) -> FunctionName -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FunctionName -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionName -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionName -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionName -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionName -> r
gmapT :: (forall b. Data b => b -> b) -> FunctionName -> FunctionName
$cgmapT :: (forall b. Data b => b -> b) -> FunctionName -> FunctionName
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FunctionName)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FunctionName)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c FunctionName)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunctionName)
dataTypeOf :: FunctionName -> DataType
$cdataTypeOf :: FunctionName -> DataType
toConstr :: FunctionName -> Constr
$ctoConstr :: FunctionName -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunctionName
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunctionName
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunctionName -> c FunctionName
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunctionName -> c FunctionName
$cp1Data :: Typeable FunctionName
Data, (forall x. FunctionName -> Rep FunctionName x)
-> (forall x. Rep FunctionName x -> FunctionName)
-> Generic FunctionName
forall x. Rep FunctionName x -> FunctionName
forall x. FunctionName -> Rep FunctionName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FunctionName x -> FunctionName
$cfrom :: forall x. FunctionName -> Rep FunctionName x
Generic, FunctionName -> ()
(FunctionName -> ()) -> NFData FunctionName
forall a. (a -> ()) -> NFData a
rnf :: FunctionName -> ()
$crnf :: FunctionName -> ()
NFData, Eq FunctionName
Eq FunctionName
-> (Accesses -> FunctionName -> FunctionName -> Bool)
-> Cacheable FunctionName
Accesses -> FunctionName -> FunctionName -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> FunctionName -> FunctionName -> Bool
$cunchanged :: Accesses -> FunctionName -> FunctionName -> Bool
$cp1Cacheable :: Eq FunctionName
Cacheable)
instance IsIdentifier FunctionName where
toIdentifier :: FunctionName -> Identifier
toIdentifier (FunctionName Text
t) = Text -> Identifier
Identifier Text
t
instance ToSQL FunctionName where
toSQL :: FunctionName -> Builder
toSQL = Identifier -> Builder
forall a. ToSQL a => a -> Builder
toSQL (Identifier -> Builder)
-> (FunctionName -> Identifier) -> FunctionName -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunctionName -> Identifier
forall a. IsIdentifier a => a -> Identifier
toIdentifier
instance ToTxt FunctionName where
toTxt :: FunctionName -> Text
toTxt = FunctionName -> Text
getFunctionTxt
instance ToErrorValue FunctionName where
toErrorValue :: FunctionName -> ErrorMessage
toErrorValue = Text -> ErrorMessage
ErrorValue.squote (Text -> ErrorMessage)
-> (FunctionName -> Text) -> FunctionName -> ErrorMessage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunctionName -> Text
getFunctionTxt
newtype SchemaName = SchemaName {SchemaName -> Text
getSchemaTxt :: Text}
deriving
( Int -> SchemaName -> ShowS
[SchemaName] -> ShowS
SchemaName -> String
(Int -> SchemaName -> ShowS)
-> (SchemaName -> String)
-> ([SchemaName] -> ShowS)
-> Show SchemaName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SchemaName] -> ShowS
$cshowList :: [SchemaName] -> ShowS
show :: SchemaName -> String
$cshow :: SchemaName -> String
showsPrec :: Int -> SchemaName -> ShowS
$cshowsPrec :: Int -> SchemaName -> ShowS
Show,
SchemaName -> SchemaName -> Bool
(SchemaName -> SchemaName -> Bool)
-> (SchemaName -> SchemaName -> Bool) -> Eq SchemaName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SchemaName -> SchemaName -> Bool
$c/= :: SchemaName -> SchemaName -> Bool
== :: SchemaName -> SchemaName -> Bool
$c== :: SchemaName -> SchemaName -> Bool
Eq,
Eq SchemaName
Eq SchemaName
-> (SchemaName -> SchemaName -> Ordering)
-> (SchemaName -> SchemaName -> Bool)
-> (SchemaName -> SchemaName -> Bool)
-> (SchemaName -> SchemaName -> Bool)
-> (SchemaName -> SchemaName -> Bool)
-> (SchemaName -> SchemaName -> SchemaName)
-> (SchemaName -> SchemaName -> SchemaName)
-> Ord SchemaName
SchemaName -> SchemaName -> Bool
SchemaName -> SchemaName -> Ordering
SchemaName -> SchemaName -> SchemaName
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 :: SchemaName -> SchemaName -> SchemaName
$cmin :: SchemaName -> SchemaName -> SchemaName
max :: SchemaName -> SchemaName -> SchemaName
$cmax :: SchemaName -> SchemaName -> SchemaName
>= :: SchemaName -> SchemaName -> Bool
$c>= :: SchemaName -> SchemaName -> Bool
> :: SchemaName -> SchemaName -> Bool
$c> :: SchemaName -> SchemaName -> Bool
<= :: SchemaName -> SchemaName -> Bool
$c<= :: SchemaName -> SchemaName -> Bool
< :: SchemaName -> SchemaName -> Bool
$c< :: SchemaName -> SchemaName -> Bool
compare :: SchemaName -> SchemaName -> Ordering
$ccompare :: SchemaName -> SchemaName -> Ordering
$cp1Ord :: Eq SchemaName
Ord,
Value -> Parser [SchemaName]
Value -> Parser SchemaName
(Value -> Parser SchemaName)
-> (Value -> Parser [SchemaName]) -> FromJSON SchemaName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SchemaName]
$cparseJSONList :: Value -> Parser [SchemaName]
parseJSON :: Value -> Parser SchemaName
$cparseJSON :: Value -> Parser SchemaName
FromJSON,
[SchemaName] -> Value
[SchemaName] -> Encoding
SchemaName -> Value
SchemaName -> Encoding
(SchemaName -> Value)
-> (SchemaName -> Encoding)
-> ([SchemaName] -> Value)
-> ([SchemaName] -> Encoding)
-> ToJSON SchemaName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SchemaName] -> Encoding
$ctoEncodingList :: [SchemaName] -> Encoding
toJSONList :: [SchemaName] -> Value
$ctoJSONList :: [SchemaName] -> Value
toEncoding :: SchemaName -> Encoding
$ctoEncoding :: SchemaName -> Encoding
toJSON :: SchemaName -> Value
$ctoJSON :: SchemaName -> Value
ToJSON,
Int -> SchemaName -> Int
SchemaName -> Int
(Int -> SchemaName -> Int)
-> (SchemaName -> Int) -> Hashable SchemaName
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: SchemaName -> Int
$chash :: SchemaName -> Int
hashWithSalt :: Int -> SchemaName -> Int
$chashWithSalt :: Int -> SchemaName -> Int
Hashable,
SchemaName -> PrepArg
(SchemaName -> PrepArg) -> ToPrepArg SchemaName
forall a. (a -> PrepArg) -> ToPrepArg a
toPrepVal :: SchemaName -> PrepArg
$ctoPrepVal :: SchemaName -> PrepArg
Q.ToPrepArg,
Maybe ByteString -> Either Text SchemaName
(Maybe ByteString -> Either Text SchemaName) -> FromCol SchemaName
forall a. (Maybe ByteString -> Either Text a) -> FromCol a
fromCol :: Maybe ByteString -> Either Text SchemaName
$cfromCol :: Maybe ByteString -> Either Text SchemaName
Q.FromCol,
Typeable SchemaName
DataType
Constr
Typeable SchemaName
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SchemaName -> c SchemaName)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SchemaName)
-> (SchemaName -> Constr)
-> (SchemaName -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SchemaName))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SchemaName))
-> ((forall b. Data b => b -> b) -> SchemaName -> SchemaName)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SchemaName -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SchemaName -> r)
-> (forall u. (forall d. Data d => d -> u) -> SchemaName -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> SchemaName -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SchemaName -> m SchemaName)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SchemaName -> m SchemaName)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SchemaName -> m SchemaName)
-> Data SchemaName
SchemaName -> DataType
SchemaName -> Constr
(forall b. Data b => b -> b) -> SchemaName -> SchemaName
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SchemaName -> c SchemaName
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SchemaName
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> SchemaName -> u
forall u. (forall d. Data d => d -> u) -> SchemaName -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SchemaName -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SchemaName -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SchemaName -> m SchemaName
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SchemaName -> m SchemaName
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SchemaName
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SchemaName -> c SchemaName
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SchemaName)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SchemaName)
$cSchemaName :: Constr
$tSchemaName :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> SchemaName -> m SchemaName
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SchemaName -> m SchemaName
gmapMp :: (forall d. Data d => d -> m d) -> SchemaName -> m SchemaName
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SchemaName -> m SchemaName
gmapM :: (forall d. Data d => d -> m d) -> SchemaName -> m SchemaName
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SchemaName -> m SchemaName
gmapQi :: Int -> (forall d. Data d => d -> u) -> SchemaName -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SchemaName -> u
gmapQ :: (forall d. Data d => d -> u) -> SchemaName -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SchemaName -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SchemaName -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SchemaName -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SchemaName -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SchemaName -> r
gmapT :: (forall b. Data b => b -> b) -> SchemaName -> SchemaName
$cgmapT :: (forall b. Data b => b -> b) -> SchemaName -> SchemaName
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SchemaName)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SchemaName)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c SchemaName)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SchemaName)
dataTypeOf :: SchemaName -> DataType
$cdataTypeOf :: SchemaName -> DataType
toConstr :: SchemaName -> Constr
$ctoConstr :: SchemaName -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SchemaName
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SchemaName
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SchemaName -> c SchemaName
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SchemaName -> c SchemaName
$cp1Data :: Typeable SchemaName
Data,
(forall x. SchemaName -> Rep SchemaName x)
-> (forall x. Rep SchemaName x -> SchemaName) -> Generic SchemaName
forall x. Rep SchemaName x -> SchemaName
forall x. SchemaName -> Rep SchemaName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SchemaName x -> SchemaName
$cfrom :: forall x. SchemaName -> Rep SchemaName x
Generic,
SchemaName -> ()
(SchemaName -> ()) -> NFData SchemaName
forall a. (a -> ()) -> NFData a
rnf :: SchemaName -> ()
$crnf :: SchemaName -> ()
NFData,
Eq SchemaName
Eq SchemaName
-> (Accesses -> SchemaName -> SchemaName -> Bool)
-> Cacheable SchemaName
Accesses -> SchemaName -> SchemaName -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> SchemaName -> SchemaName -> Bool
$cunchanged :: Accesses -> SchemaName -> SchemaName -> Bool
$cp1Cacheable :: Eq SchemaName
Cacheable,
String -> SchemaName
(String -> SchemaName) -> IsString SchemaName
forall a. (String -> a) -> IsString a
fromString :: String -> SchemaName
$cfromString :: String -> SchemaName
IsString
)
publicSchema :: SchemaName
publicSchema :: SchemaName
publicSchema = Text -> SchemaName
SchemaName Text
"public"
hdbCatalogSchema :: SchemaName
hdbCatalogSchema :: SchemaName
hdbCatalogSchema = Text -> SchemaName
SchemaName Text
"hdb_catalog"
instance IsIdentifier SchemaName where
toIdentifier :: SchemaName -> Identifier
toIdentifier (SchemaName Text
t) = Text -> Identifier
Identifier Text
t
instance ToSQL SchemaName where
toSQL :: SchemaName -> Builder
toSQL = Identifier -> Builder
forall a. ToSQL a => a -> Builder
toSQL (Identifier -> Builder)
-> (SchemaName -> Identifier) -> SchemaName -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SchemaName -> Identifier
forall a. IsIdentifier a => a -> Identifier
toIdentifier
data QualifiedObject a = QualifiedObject
{ QualifiedObject a -> SchemaName
qSchema :: SchemaName,
QualifiedObject a -> a
qName :: a
}
deriving (Int -> QualifiedObject a -> ShowS
[QualifiedObject a] -> ShowS
QualifiedObject a -> String
(Int -> QualifiedObject a -> ShowS)
-> (QualifiedObject a -> String)
-> ([QualifiedObject a] -> ShowS)
-> Show (QualifiedObject a)
forall a. Show a => Int -> QualifiedObject a -> ShowS
forall a. Show a => [QualifiedObject a] -> ShowS
forall a. Show a => QualifiedObject a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QualifiedObject a] -> ShowS
$cshowList :: forall a. Show a => [QualifiedObject a] -> ShowS
show :: QualifiedObject a -> String
$cshow :: forall a. Show a => QualifiedObject a -> String
showsPrec :: Int -> QualifiedObject a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> QualifiedObject a -> ShowS
Show, QualifiedObject a -> QualifiedObject a -> Bool
(QualifiedObject a -> QualifiedObject a -> Bool)
-> (QualifiedObject a -> QualifiedObject a -> Bool)
-> Eq (QualifiedObject a)
forall a. Eq a => QualifiedObject a -> QualifiedObject a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QualifiedObject a -> QualifiedObject a -> Bool
$c/= :: forall a. Eq a => QualifiedObject a -> QualifiedObject a -> Bool
== :: QualifiedObject a -> QualifiedObject a -> Bool
$c== :: forall a. Eq a => QualifiedObject a -> QualifiedObject a -> Bool
Eq, a -> QualifiedObject b -> QualifiedObject a
(a -> b) -> QualifiedObject a -> QualifiedObject b
(forall a b. (a -> b) -> QualifiedObject a -> QualifiedObject b)
-> (forall a b. a -> QualifiedObject b -> QualifiedObject a)
-> Functor QualifiedObject
forall a b. a -> QualifiedObject b -> QualifiedObject a
forall a b. (a -> b) -> QualifiedObject a -> QualifiedObject b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> QualifiedObject b -> QualifiedObject a
$c<$ :: forall a b. a -> QualifiedObject b -> QualifiedObject a
fmap :: (a -> b) -> QualifiedObject a -> QualifiedObject b
$cfmap :: forall a b. (a -> b) -> QualifiedObject a -> QualifiedObject b
Functor, Eq (QualifiedObject a)
Eq (QualifiedObject a)
-> (QualifiedObject a -> QualifiedObject a -> Ordering)
-> (QualifiedObject a -> QualifiedObject a -> Bool)
-> (QualifiedObject a -> QualifiedObject a -> Bool)
-> (QualifiedObject a -> QualifiedObject a -> Bool)
-> (QualifiedObject a -> QualifiedObject a -> Bool)
-> (QualifiedObject a -> QualifiedObject a -> QualifiedObject a)
-> (QualifiedObject a -> QualifiedObject a -> QualifiedObject a)
-> Ord (QualifiedObject a)
QualifiedObject a -> QualifiedObject a -> Bool
QualifiedObject a -> QualifiedObject a -> Ordering
QualifiedObject a -> QualifiedObject a -> QualifiedObject a
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
forall a. Ord a => Eq (QualifiedObject a)
forall a. Ord a => QualifiedObject a -> QualifiedObject a -> Bool
forall a.
Ord a =>
QualifiedObject a -> QualifiedObject a -> Ordering
forall a.
Ord a =>
QualifiedObject a -> QualifiedObject a -> QualifiedObject a
min :: QualifiedObject a -> QualifiedObject a -> QualifiedObject a
$cmin :: forall a.
Ord a =>
QualifiedObject a -> QualifiedObject a -> QualifiedObject a
max :: QualifiedObject a -> QualifiedObject a -> QualifiedObject a
$cmax :: forall a.
Ord a =>
QualifiedObject a -> QualifiedObject a -> QualifiedObject a
>= :: QualifiedObject a -> QualifiedObject a -> Bool
$c>= :: forall a. Ord a => QualifiedObject a -> QualifiedObject a -> Bool
> :: QualifiedObject a -> QualifiedObject a -> Bool
$c> :: forall a. Ord a => QualifiedObject a -> QualifiedObject a -> Bool
<= :: QualifiedObject a -> QualifiedObject a -> Bool
$c<= :: forall a. Ord a => QualifiedObject a -> QualifiedObject a -> Bool
< :: QualifiedObject a -> QualifiedObject a -> Bool
$c< :: forall a. Ord a => QualifiedObject a -> QualifiedObject a -> Bool
compare :: QualifiedObject a -> QualifiedObject a -> Ordering
$ccompare :: forall a.
Ord a =>
QualifiedObject a -> QualifiedObject a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (QualifiedObject a)
Ord, (forall x. QualifiedObject a -> Rep (QualifiedObject a) x)
-> (forall x. Rep (QualifiedObject a) x -> QualifiedObject a)
-> Generic (QualifiedObject a)
forall x. Rep (QualifiedObject a) x -> QualifiedObject a
forall x. QualifiedObject a -> Rep (QualifiedObject a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (QualifiedObject a) x -> QualifiedObject a
forall a x. QualifiedObject a -> Rep (QualifiedObject a) x
$cto :: forall a x. Rep (QualifiedObject a) x -> QualifiedObject a
$cfrom :: forall a x. QualifiedObject a -> Rep (QualifiedObject a) x
Generic, Typeable (QualifiedObject a)
DataType
Constr
Typeable (QualifiedObject a)
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> QualifiedObject a
-> c (QualifiedObject a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (QualifiedObject a))
-> (QualifiedObject a -> Constr)
-> (QualifiedObject a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (QualifiedObject a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (QualifiedObject a)))
-> ((forall b. Data b => b -> b)
-> QualifiedObject a -> QualifiedObject a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QualifiedObject a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QualifiedObject a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> QualifiedObject a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> QualifiedObject a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> QualifiedObject a -> m (QualifiedObject a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> QualifiedObject a -> m (QualifiedObject a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> QualifiedObject a -> m (QualifiedObject a))
-> Data (QualifiedObject a)
QualifiedObject a -> DataType
QualifiedObject a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (QualifiedObject a))
(forall b. Data b => b -> b)
-> QualifiedObject a -> QualifiedObject a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> QualifiedObject a
-> c (QualifiedObject a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (QualifiedObject a)
forall a. Data a => Typeable (QualifiedObject a)
forall a. Data a => QualifiedObject a -> DataType
forall a. Data a => QualifiedObject a -> Constr
forall a.
Data a =>
(forall b. Data b => b -> b)
-> QualifiedObject a -> QualifiedObject a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> QualifiedObject a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> QualifiedObject a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QualifiedObject a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QualifiedObject a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> QualifiedObject a -> m (QualifiedObject a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> QualifiedObject a -> m (QualifiedObject a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (QualifiedObject a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> QualifiedObject a
-> c (QualifiedObject a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (QualifiedObject a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (QualifiedObject a))
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> QualifiedObject a -> u
forall u. (forall d. Data d => d -> u) -> QualifiedObject a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QualifiedObject a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QualifiedObject a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> QualifiedObject a -> m (QualifiedObject a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> QualifiedObject a -> m (QualifiedObject a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (QualifiedObject a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> QualifiedObject a
-> c (QualifiedObject a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (QualifiedObject a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (QualifiedObject a))
$cQualifiedObject :: Constr
$tQualifiedObject :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> QualifiedObject a -> m (QualifiedObject a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> QualifiedObject a -> m (QualifiedObject a)
gmapMp :: (forall d. Data d => d -> m d)
-> QualifiedObject a -> m (QualifiedObject a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> QualifiedObject a -> m (QualifiedObject a)
gmapM :: (forall d. Data d => d -> m d)
-> QualifiedObject a -> m (QualifiedObject a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> QualifiedObject a -> m (QualifiedObject a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> QualifiedObject a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> QualifiedObject a -> u
gmapQ :: (forall d. Data d => d -> u) -> QualifiedObject a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> QualifiedObject a -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QualifiedObject a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QualifiedObject a -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QualifiedObject a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QualifiedObject a -> r
gmapT :: (forall b. Data b => b -> b)
-> QualifiedObject a -> QualifiedObject a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> QualifiedObject a -> QualifiedObject a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (QualifiedObject a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (QualifiedObject a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (QualifiedObject a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (QualifiedObject a))
dataTypeOf :: QualifiedObject a -> DataType
$cdataTypeOf :: forall a. Data a => QualifiedObject a -> DataType
toConstr :: QualifiedObject a -> Constr
$ctoConstr :: forall a. Data a => QualifiedObject a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (QualifiedObject a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (QualifiedObject a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> QualifiedObject a
-> c (QualifiedObject a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> QualifiedObject a
-> c (QualifiedObject a)
$cp1Data :: forall a. Data a => Typeable (QualifiedObject a)
Data)
instance (NFData a) => NFData (QualifiedObject a)
instance (Cacheable a) => Cacheable (QualifiedObject a)
instance (FromJSON a) => FromJSON (QualifiedObject a) where
parseJSON :: Value -> Parser (QualifiedObject a)
parseJSON v :: Value
v@(String Text
_) =
SchemaName -> a -> QualifiedObject a
forall a. SchemaName -> a -> QualifiedObject a
QualifiedObject SchemaName
publicSchema (a -> QualifiedObject a) -> Parser a -> Parser (QualifiedObject a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser a
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
parseJSON (Object Object
o) =
SchemaName -> a -> QualifiedObject a
forall a. SchemaName -> a -> QualifiedObject a
QualifiedObject
(SchemaName -> a -> QualifiedObject a)
-> Parser SchemaName -> Parser (a -> QualifiedObject a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe SchemaName)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"schema" Parser (Maybe SchemaName) -> SchemaName -> Parser SchemaName
forall a. Parser (Maybe a) -> a -> Parser a
.!= SchemaName
publicSchema
Parser (a -> QualifiedObject a)
-> Parser a -> Parser (QualifiedObject a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser a
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
parseJSON Value
_ =
String -> Parser (QualifiedObject a)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"expecting a string/object for QualifiedObject"
instance (ToJSON a) => ToJSON (QualifiedObject a) where
toJSON :: QualifiedObject a -> Value
toJSON (QualifiedObject SchemaName
sn a
o) =
[Pair] -> Value
object
[ Key
"schema" Key -> SchemaName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= SchemaName
sn,
Key
"name" Key -> a -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= a
o
]
instance (ToJSON a, ToTxt a) => ToJSONKey (QualifiedObject a) where
toJSONKey :: ToJSONKeyFunction (QualifiedObject a)
toJSONKey = (QualifiedObject a -> Key)
-> (QualifiedObject a -> Encoding' Key)
-> ToJSONKeyFunction (QualifiedObject a)
forall a. (a -> Key) -> (a -> Encoding' Key) -> ToJSONKeyFunction a
ToJSONKeyText (Text -> Key
K.fromText (Text -> Key)
-> (QualifiedObject a -> Text) -> QualifiedObject a -> Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QualifiedObject a -> Text
forall a. ToTxt a => QualifiedObject a -> Text
qualifiedObjectToText) (Text -> Encoding' Key
forall a. Text -> Encoding' a
text (Text -> Encoding' Key)
-> (QualifiedObject a -> Text)
-> QualifiedObject a
-> Encoding' Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QualifiedObject a -> Text
forall a. ToTxt a => QualifiedObject a -> Text
qualifiedObjectToText)
instance ToTxt a => ToTxt (QualifiedObject a) where
toTxt :: QualifiedObject a -> Text
toTxt = QualifiedObject a -> Text
forall a. ToTxt a => QualifiedObject a -> Text
qualifiedObjectToText
instance ToTxt a => ToErrorValue (QualifiedObject a) where
toErrorValue :: QualifiedObject a -> ErrorMessage
toErrorValue (QualifiedObject SchemaName
sn a
o) = Text -> ErrorMessage
ErrorValue.squote (Text -> ErrorMessage) -> Text -> ErrorMessage
forall a b. (a -> b) -> a -> b
$ SchemaName -> Text
getSchemaTxt SchemaName
sn Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
forall a. ToTxt a => a -> Text
toTxt a
o
instance (Hashable a) => Hashable (QualifiedObject a)
instance (ToSQL a) => ToSQL (QualifiedObject a) where
toSQL :: QualifiedObject a -> Builder
toSQL (QualifiedObject SchemaName
sn a
o) =
SchemaName -> Builder
forall a. ToSQL a => a -> Builder
toSQL SchemaName
sn Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
"." Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> a -> Builder
forall a. ToSQL a => a -> Builder
toSQL a
o
qualifiedObjectToText :: ToTxt a => QualifiedObject a -> Text
qualifiedObjectToText :: QualifiedObject a -> Text
qualifiedObjectToText (QualifiedObject SchemaName
sn a
o)
| SchemaName
sn SchemaName -> SchemaName -> Bool
forall a. Eq a => a -> a -> Bool
== SchemaName
publicSchema = a -> Text
forall a. ToTxt a => a -> Text
toTxt a
o
| Bool
otherwise = SchemaName -> Text
getSchemaTxt SchemaName
sn Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
forall a. ToTxt a => a -> Text
toTxt a
o
snakeCaseQualifiedObject :: ToTxt a => QualifiedObject a -> Text
snakeCaseQualifiedObject :: QualifiedObject a -> Text
snakeCaseQualifiedObject (QualifiedObject SchemaName
sn a
o)
| SchemaName
sn SchemaName -> SchemaName -> Bool
forall a. Eq a => a -> a -> Bool
== SchemaName
publicSchema = a -> Text
forall a. ToTxt a => a -> Text
toTxt a
o
| Bool
otherwise = SchemaName -> Text
getSchemaTxt SchemaName
sn Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
forall a. ToTxt a => a -> Text
toTxt a
o
getIdentifierQualifiedObject :: ToTxt a => QualifiedObject a -> Either QErr C.GQLNameIdentifier
getIdentifierQualifiedObject :: QualifiedObject a -> Either QErr GQLNameIdentifier
getIdentifierQualifiedObject obj :: QualifiedObject a
obj@(QualifiedObject SchemaName
sn a
o) = do
let tLst :: [Text]
tLst =
if SchemaName
sn SchemaName -> SchemaName -> Bool
forall a. Eq a => a -> a -> Bool
== SchemaName
publicSchema
then Text -> [Text]
C.fromSnake (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ a -> Text
forall a. ToTxt a => a -> Text
toTxt a
o
else Text -> [Text]
C.fromSnake (SchemaName -> Text
getSchemaTxt SchemaName
sn) [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> Text -> [Text]
C.fromSnake (a -> Text
forall a. ToTxt a => a -> Text
toTxt a
o)
gqlIdents :: Maybe GQLNameIdentifier
gqlIdents = do
(Text
pref, [Text]
suffs) <- [Text] -> Maybe (Text, [Text])
forall a. [a] -> Maybe (a, [a])
uncons [Text]
tLst
Name
prefName <- Text -> Maybe Name
G.mkName Text
pref
[NameSuffix]
suffNames <- (Text -> Maybe NameSuffix) -> [Text] -> Maybe [NameSuffix]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Text -> Maybe NameSuffix
G.mkNameSuffix [Text]
suffs
GQLNameIdentifier -> Maybe GQLNameIdentifier
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GQLNameIdentifier -> Maybe GQLNameIdentifier)
-> GQLNameIdentifier -> Maybe GQLNameIdentifier
forall a b. (a -> b) -> a -> b
$ (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple (Name
prefName, [NameSuffix]
suffNames)
Maybe GQLNameIdentifier
gqlIdents
Maybe GQLNameIdentifier
-> Either QErr GQLNameIdentifier -> Either QErr GQLNameIdentifier
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` Code -> Text -> Either QErr GQLNameIdentifier
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400
Code
ValidationFailed
( Text
"cannot include " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> QualifiedObject a
obj QualifiedObject a -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" in the GraphQL schema because " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
C.toSnakeT [Text]
tLst
Text -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" is not a valid GraphQL identifier"
)
namingConventionSupport :: SupportedNamingCase
namingConventionSupport :: SupportedNamingCase
namingConventionSupport = SupportedNamingCase
AllConventions
qualifiedObjectToName :: (ToTxt a, MonadError QErr m) => QualifiedObject a -> m G.Name
qualifiedObjectToName :: QualifiedObject a -> m Name
qualifiedObjectToName QualifiedObject a
objectName = do
let textName :: Text
textName = QualifiedObject a -> Text
forall a. ToTxt a => QualifiedObject a -> Text
snakeCaseQualifiedObject QualifiedObject a
objectName
Maybe Name -> m Name -> m Name
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
onNothing (Text -> Maybe Name
G.mkName Text
textName) (m Name -> m Name) -> m Name -> m Name
forall a b. (a -> b) -> a -> b
$
Code -> Text -> m Name
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
ValidationFailed (Text -> m Name) -> Text -> m Name
forall a b. (a -> b) -> a -> b
$
Text
"cannot include " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> QualifiedObject a
objectName QualifiedObject a -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" in the GraphQL schema because " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
textName
Text -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" is not a valid GraphQL identifier"
type QualifiedTable = QualifiedObject TableName
type QualifiedFunction = QualifiedObject FunctionName
newtype PGDescription = PGDescription {PGDescription -> Text
getPGDescription :: Text}
deriving (Int -> PGDescription -> ShowS
[PGDescription] -> ShowS
PGDescription -> String
(Int -> PGDescription -> ShowS)
-> (PGDescription -> String)
-> ([PGDescription] -> ShowS)
-> Show PGDescription
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PGDescription] -> ShowS
$cshowList :: [PGDescription] -> ShowS
show :: PGDescription -> String
$cshow :: PGDescription -> String
showsPrec :: Int -> PGDescription -> ShowS
$cshowsPrec :: Int -> PGDescription -> ShowS
Show, PGDescription -> PGDescription -> Bool
(PGDescription -> PGDescription -> Bool)
-> (PGDescription -> PGDescription -> Bool) -> Eq PGDescription
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PGDescription -> PGDescription -> Bool
$c/= :: PGDescription -> PGDescription -> Bool
== :: PGDescription -> PGDescription -> Bool
$c== :: PGDescription -> PGDescription -> Bool
Eq, Value -> Parser [PGDescription]
Value -> Parser PGDescription
(Value -> Parser PGDescription)
-> (Value -> Parser [PGDescription]) -> FromJSON PGDescription
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PGDescription]
$cparseJSONList :: Value -> Parser [PGDescription]
parseJSON :: Value -> Parser PGDescription
$cparseJSON :: Value -> Parser PGDescription
FromJSON, [PGDescription] -> Value
[PGDescription] -> Encoding
PGDescription -> Value
PGDescription -> Encoding
(PGDescription -> Value)
-> (PGDescription -> Encoding)
-> ([PGDescription] -> Value)
-> ([PGDescription] -> Encoding)
-> ToJSON PGDescription
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PGDescription] -> Encoding
$ctoEncodingList :: [PGDescription] -> Encoding
toJSONList :: [PGDescription] -> Value
$ctoJSONList :: [PGDescription] -> Value
toEncoding :: PGDescription -> Encoding
$ctoEncoding :: PGDescription -> Encoding
toJSON :: PGDescription -> Value
$ctoJSON :: PGDescription -> Value
ToJSON, Maybe ByteString -> Either Text PGDescription
(Maybe ByteString -> Either Text PGDescription)
-> FromCol PGDescription
forall a. (Maybe ByteString -> Either Text a) -> FromCol a
fromCol :: Maybe ByteString -> Either Text PGDescription
$cfromCol :: Maybe ByteString -> Either Text PGDescription
Q.FromCol, PGDescription -> ()
(PGDescription -> ()) -> NFData PGDescription
forall a. (a -> ()) -> NFData a
rnf :: PGDescription -> ()
$crnf :: PGDescription -> ()
NFData, Eq PGDescription
Eq PGDescription
-> (Accesses -> PGDescription -> PGDescription -> Bool)
-> Cacheable PGDescription
Accesses -> PGDescription -> PGDescription -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> PGDescription -> PGDescription -> Bool
$cunchanged :: Accesses -> PGDescription -> PGDescription -> Bool
$cp1Cacheable :: Eq PGDescription
Cacheable, Int -> PGDescription -> Int
PGDescription -> Int
(Int -> PGDescription -> Int)
-> (PGDescription -> Int) -> Hashable PGDescription
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: PGDescription -> Int
$chash :: PGDescription -> Int
hashWithSalt :: Int -> PGDescription -> Int
$chashWithSalt :: Int -> PGDescription -> Int
Hashable)
newtype PGCol = PGCol {PGCol -> Text
getPGColTxt :: Text}
deriving
( Int -> PGCol -> ShowS
[PGCol] -> ShowS
PGCol -> String
(Int -> PGCol -> ShowS)
-> (PGCol -> String) -> ([PGCol] -> ShowS) -> Show PGCol
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PGCol] -> ShowS
$cshowList :: [PGCol] -> ShowS
show :: PGCol -> String
$cshow :: PGCol -> String
showsPrec :: Int -> PGCol -> ShowS
$cshowsPrec :: Int -> PGCol -> ShowS
Show,
PGCol -> PGCol -> Bool
(PGCol -> PGCol -> Bool) -> (PGCol -> PGCol -> Bool) -> Eq PGCol
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PGCol -> PGCol -> Bool
$c/= :: PGCol -> PGCol -> Bool
== :: PGCol -> PGCol -> Bool
$c== :: PGCol -> PGCol -> Bool
Eq,
Eq PGCol
Eq PGCol
-> (PGCol -> PGCol -> Ordering)
-> (PGCol -> PGCol -> Bool)
-> (PGCol -> PGCol -> Bool)
-> (PGCol -> PGCol -> Bool)
-> (PGCol -> PGCol -> Bool)
-> (PGCol -> PGCol -> PGCol)
-> (PGCol -> PGCol -> PGCol)
-> Ord PGCol
PGCol -> PGCol -> Bool
PGCol -> PGCol -> Ordering
PGCol -> PGCol -> PGCol
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 :: PGCol -> PGCol -> PGCol
$cmin :: PGCol -> PGCol -> PGCol
max :: PGCol -> PGCol -> PGCol
$cmax :: PGCol -> PGCol -> PGCol
>= :: PGCol -> PGCol -> Bool
$c>= :: PGCol -> PGCol -> Bool
> :: PGCol -> PGCol -> Bool
$c> :: PGCol -> PGCol -> Bool
<= :: PGCol -> PGCol -> Bool
$c<= :: PGCol -> PGCol -> Bool
< :: PGCol -> PGCol -> Bool
$c< :: PGCol -> PGCol -> Bool
compare :: PGCol -> PGCol -> Ordering
$ccompare :: PGCol -> PGCol -> Ordering
$cp1Ord :: Eq PGCol
Ord,
Value -> Parser [PGCol]
Value -> Parser PGCol
(Value -> Parser PGCol)
-> (Value -> Parser [PGCol]) -> FromJSON PGCol
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PGCol]
$cparseJSONList :: Value -> Parser [PGCol]
parseJSON :: Value -> Parser PGCol
$cparseJSON :: Value -> Parser PGCol
FromJSON,
[PGCol] -> Value
[PGCol] -> Encoding
PGCol -> Value
PGCol -> Encoding
(PGCol -> Value)
-> (PGCol -> Encoding)
-> ([PGCol] -> Value)
-> ([PGCol] -> Encoding)
-> ToJSON PGCol
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PGCol] -> Encoding
$ctoEncodingList :: [PGCol] -> Encoding
toJSONList :: [PGCol] -> Value
$ctoJSONList :: [PGCol] -> Value
toEncoding :: PGCol -> Encoding
$ctoEncoding :: PGCol -> Encoding
toJSON :: PGCol -> Value
$ctoJSON :: PGCol -> Value
ToJSON,
Int -> PGCol -> Int
PGCol -> Int
(Int -> PGCol -> Int) -> (PGCol -> Int) -> Hashable PGCol
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: PGCol -> Int
$chash :: PGCol -> Int
hashWithSalt :: Int -> PGCol -> Int
$chashWithSalt :: Int -> PGCol -> Int
Hashable,
PGCol -> PrepArg
(PGCol -> PrepArg) -> ToPrepArg PGCol
forall a. (a -> PrepArg) -> ToPrepArg a
toPrepVal :: PGCol -> PrepArg
$ctoPrepVal :: PGCol -> PrepArg
Q.ToPrepArg,
Maybe ByteString -> Either Text PGCol
(Maybe ByteString -> Either Text PGCol) -> FromCol PGCol
forall a. (Maybe ByteString -> Either Text a) -> FromCol a
fromCol :: Maybe ByteString -> Either Text PGCol
$cfromCol :: Maybe ByteString -> Either Text PGCol
Q.FromCol,
ToJSONKeyFunction [PGCol]
ToJSONKeyFunction PGCol
ToJSONKeyFunction PGCol
-> ToJSONKeyFunction [PGCol] -> ToJSONKey PGCol
forall a.
ToJSONKeyFunction a -> ToJSONKeyFunction [a] -> ToJSONKey a
toJSONKeyList :: ToJSONKeyFunction [PGCol]
$ctoJSONKeyList :: ToJSONKeyFunction [PGCol]
toJSONKey :: ToJSONKeyFunction PGCol
$ctoJSONKey :: ToJSONKeyFunction PGCol
ToJSONKey,
FromJSONKeyFunction [PGCol]
FromJSONKeyFunction PGCol
FromJSONKeyFunction PGCol
-> FromJSONKeyFunction [PGCol] -> FromJSONKey PGCol
forall a.
FromJSONKeyFunction a -> FromJSONKeyFunction [a] -> FromJSONKey a
fromJSONKeyList :: FromJSONKeyFunction [PGCol]
$cfromJSONKeyList :: FromJSONKeyFunction [PGCol]
fromJSONKey :: FromJSONKeyFunction PGCol
$cfromJSONKey :: FromJSONKeyFunction PGCol
FromJSONKey,
Typeable PGCol
DataType
Constr
Typeable PGCol
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PGCol -> c PGCol)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PGCol)
-> (PGCol -> Constr)
-> (PGCol -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PGCol))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PGCol))
-> ((forall b. Data b => b -> b) -> PGCol -> PGCol)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PGCol -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PGCol -> r)
-> (forall u. (forall d. Data d => d -> u) -> PGCol -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> PGCol -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PGCol -> m PGCol)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PGCol -> m PGCol)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PGCol -> m PGCol)
-> Data PGCol
PGCol -> DataType
PGCol -> Constr
(forall b. Data b => b -> b) -> PGCol -> PGCol
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PGCol -> c PGCol
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PGCol
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> PGCol -> u
forall u. (forall d. Data d => d -> u) -> PGCol -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PGCol -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PGCol -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PGCol -> m PGCol
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PGCol -> m PGCol
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PGCol
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PGCol -> c PGCol
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PGCol)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PGCol)
$cPGCol :: Constr
$tPGCol :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> PGCol -> m PGCol
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PGCol -> m PGCol
gmapMp :: (forall d. Data d => d -> m d) -> PGCol -> m PGCol
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PGCol -> m PGCol
gmapM :: (forall d. Data d => d -> m d) -> PGCol -> m PGCol
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PGCol -> m PGCol
gmapQi :: Int -> (forall d. Data d => d -> u) -> PGCol -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PGCol -> u
gmapQ :: (forall d. Data d => d -> u) -> PGCol -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PGCol -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PGCol -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PGCol -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PGCol -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PGCol -> r
gmapT :: (forall b. Data b => b -> b) -> PGCol -> PGCol
$cgmapT :: (forall b. Data b => b -> b) -> PGCol -> PGCol
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PGCol)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PGCol)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c PGCol)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PGCol)
dataTypeOf :: PGCol -> DataType
$cdataTypeOf :: PGCol -> DataType
toConstr :: PGCol -> Constr
$ctoConstr :: PGCol -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PGCol
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PGCol
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PGCol -> c PGCol
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PGCol -> c PGCol
$cp1Data :: Typeable PGCol
Data,
(forall x. PGCol -> Rep PGCol x)
-> (forall x. Rep PGCol x -> PGCol) -> Generic PGCol
forall x. Rep PGCol x -> PGCol
forall x. PGCol -> Rep PGCol x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PGCol x -> PGCol
$cfrom :: forall x. PGCol -> Rep PGCol x
Generic,
PGCol -> ()
(PGCol -> ()) -> NFData PGCol
forall a. (a -> ()) -> NFData a
rnf :: PGCol -> ()
$crnf :: PGCol -> ()
NFData,
Eq PGCol
Eq PGCol -> (Accesses -> PGCol -> PGCol -> Bool) -> Cacheable PGCol
Accesses -> PGCol -> PGCol -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> PGCol -> PGCol -> Bool
$cunchanged :: Accesses -> PGCol -> PGCol -> Bool
$cp1Cacheable :: Eq PGCol
Cacheable,
String -> PGCol
(String -> PGCol) -> IsString PGCol
forall a. (String -> a) -> IsString a
fromString :: String -> PGCol
$cfromString :: String -> PGCol
IsString
)
instance IsIdentifier PGCol where
toIdentifier :: PGCol -> Identifier
toIdentifier (PGCol Text
t) = Text -> Identifier
Identifier Text
t
instance ToSQL PGCol where
toSQL :: PGCol -> Builder
toSQL = Identifier -> Builder
forall a. ToSQL a => a -> Builder
toSQL (Identifier -> Builder)
-> (PGCol -> Identifier) -> PGCol -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PGCol -> Identifier
forall a. IsIdentifier a => a -> Identifier
toIdentifier
instance ToTxt PGCol where
toTxt :: PGCol -> Text
toTxt = PGCol -> Text
getPGColTxt
instance ToErrorValue PGCol where
toErrorValue :: PGCol -> ErrorMessage
toErrorValue = Text -> ErrorMessage
ErrorValue.squote (Text -> ErrorMessage) -> (PGCol -> Text) -> PGCol -> ErrorMessage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PGCol -> Text
getPGColTxt
unsafePGCol :: Text -> PGCol
unsafePGCol :: Text -> PGCol
unsafePGCol = Text -> PGCol
PGCol
showPGCols :: (Foldable t, Functor t) => t PGCol -> T.Text
showPGCols :: t PGCol -> Text
showPGCols = t Text -> Text
forall t (f :: * -> *). (ToTxt t, Foldable f) => f t -> Text
dquoteList (t Text -> Text) -> (t PGCol -> t Text) -> t PGCol -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PGCol -> Text) -> t PGCol -> t Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PGCol -> Text
getPGColTxt
data PGScalarType
= PGSmallInt
| PGInteger
| PGBigInt
| PGSerial
| PGBigSerial
| PGFloat
| PGDouble
| PGNumeric
| PGMoney
| PGBoolean
| PGChar
| PGVarchar
| PGText
| PGCitext
| PGDate
| PGTimeStamp
| PGTimeStampTZ
| PGTimeTZ
| PGJSON
| PGJSONB
| PGGeometry
| PGGeography
| PGRaster
| PGUUID
| PGLtree
| PGLquery
| PGLtxtquery
| PGArray PGScalarType
| PGUnknown Text
| PGCompositeScalar Text
| PGEnumScalar Text
deriving (Int -> PGScalarType -> ShowS
[PGScalarType] -> ShowS
PGScalarType -> String
(Int -> PGScalarType -> ShowS)
-> (PGScalarType -> String)
-> ([PGScalarType] -> ShowS)
-> Show PGScalarType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PGScalarType] -> ShowS
$cshowList :: [PGScalarType] -> ShowS
show :: PGScalarType -> String
$cshow :: PGScalarType -> String
showsPrec :: Int -> PGScalarType -> ShowS
$cshowsPrec :: Int -> PGScalarType -> ShowS
Show, PGScalarType -> PGScalarType -> Bool
(PGScalarType -> PGScalarType -> Bool)
-> (PGScalarType -> PGScalarType -> Bool) -> Eq PGScalarType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PGScalarType -> PGScalarType -> Bool
$c/= :: PGScalarType -> PGScalarType -> Bool
== :: PGScalarType -> PGScalarType -> Bool
$c== :: PGScalarType -> PGScalarType -> Bool
Eq, Eq PGScalarType
Eq PGScalarType
-> (PGScalarType -> PGScalarType -> Ordering)
-> (PGScalarType -> PGScalarType -> Bool)
-> (PGScalarType -> PGScalarType -> Bool)
-> (PGScalarType -> PGScalarType -> Bool)
-> (PGScalarType -> PGScalarType -> Bool)
-> (PGScalarType -> PGScalarType -> PGScalarType)
-> (PGScalarType -> PGScalarType -> PGScalarType)
-> Ord PGScalarType
PGScalarType -> PGScalarType -> Bool
PGScalarType -> PGScalarType -> Ordering
PGScalarType -> PGScalarType -> PGScalarType
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 :: PGScalarType -> PGScalarType -> PGScalarType
$cmin :: PGScalarType -> PGScalarType -> PGScalarType
max :: PGScalarType -> PGScalarType -> PGScalarType
$cmax :: PGScalarType -> PGScalarType -> PGScalarType
>= :: PGScalarType -> PGScalarType -> Bool
$c>= :: PGScalarType -> PGScalarType -> Bool
> :: PGScalarType -> PGScalarType -> Bool
$c> :: PGScalarType -> PGScalarType -> Bool
<= :: PGScalarType -> PGScalarType -> Bool
$c<= :: PGScalarType -> PGScalarType -> Bool
< :: PGScalarType -> PGScalarType -> Bool
$c< :: PGScalarType -> PGScalarType -> Bool
compare :: PGScalarType -> PGScalarType -> Ordering
$ccompare :: PGScalarType -> PGScalarType -> Ordering
$cp1Ord :: Eq PGScalarType
Ord, (forall x. PGScalarType -> Rep PGScalarType x)
-> (forall x. Rep PGScalarType x -> PGScalarType)
-> Generic PGScalarType
forall x. Rep PGScalarType x -> PGScalarType
forall x. PGScalarType -> Rep PGScalarType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PGScalarType x -> PGScalarType
$cfrom :: forall x. PGScalarType -> Rep PGScalarType x
Generic, Typeable PGScalarType
DataType
Constr
Typeable PGScalarType
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PGScalarType -> c PGScalarType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PGScalarType)
-> (PGScalarType -> Constr)
-> (PGScalarType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PGScalarType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PGScalarType))
-> ((forall b. Data b => b -> b) -> PGScalarType -> PGScalarType)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PGScalarType -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PGScalarType -> r)
-> (forall u. (forall d. Data d => d -> u) -> PGScalarType -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> PGScalarType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PGScalarType -> m PGScalarType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PGScalarType -> m PGScalarType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PGScalarType -> m PGScalarType)
-> Data PGScalarType
PGScalarType -> DataType
PGScalarType -> Constr
(forall b. Data b => b -> b) -> PGScalarType -> PGScalarType
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PGScalarType -> c PGScalarType
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PGScalarType
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> PGScalarType -> u
forall u. (forall d. Data d => d -> u) -> PGScalarType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PGScalarType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PGScalarType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PGScalarType -> m PGScalarType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PGScalarType -> m PGScalarType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PGScalarType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PGScalarType -> c PGScalarType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PGScalarType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PGScalarType)
$cPGEnumScalar :: Constr
$cPGCompositeScalar :: Constr
$cPGUnknown :: Constr
$cPGArray :: Constr
$cPGLtxtquery :: Constr
$cPGLquery :: Constr
$cPGLtree :: Constr
$cPGUUID :: Constr
$cPGRaster :: Constr
$cPGGeography :: Constr
$cPGGeometry :: Constr
$cPGJSONB :: Constr
$cPGJSON :: Constr
$cPGTimeTZ :: Constr
$cPGTimeStampTZ :: Constr
$cPGTimeStamp :: Constr
$cPGDate :: Constr
$cPGCitext :: Constr
$cPGText :: Constr
$cPGVarchar :: Constr
$cPGChar :: Constr
$cPGBoolean :: Constr
$cPGMoney :: Constr
$cPGNumeric :: Constr
$cPGDouble :: Constr
$cPGFloat :: Constr
$cPGBigSerial :: Constr
$cPGSerial :: Constr
$cPGBigInt :: Constr
$cPGInteger :: Constr
$cPGSmallInt :: Constr
$tPGScalarType :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> PGScalarType -> m PGScalarType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PGScalarType -> m PGScalarType
gmapMp :: (forall d. Data d => d -> m d) -> PGScalarType -> m PGScalarType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PGScalarType -> m PGScalarType
gmapM :: (forall d. Data d => d -> m d) -> PGScalarType -> m PGScalarType
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PGScalarType -> m PGScalarType
gmapQi :: Int -> (forall d. Data d => d -> u) -> PGScalarType -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PGScalarType -> u
gmapQ :: (forall d. Data d => d -> u) -> PGScalarType -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PGScalarType -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PGScalarType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PGScalarType -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PGScalarType -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PGScalarType -> r
gmapT :: (forall b. Data b => b -> b) -> PGScalarType -> PGScalarType
$cgmapT :: (forall b. Data b => b -> b) -> PGScalarType -> PGScalarType
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PGScalarType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PGScalarType)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c PGScalarType)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PGScalarType)
dataTypeOf :: PGScalarType -> DataType
$cdataTypeOf :: PGScalarType -> DataType
toConstr :: PGScalarType -> Constr
$ctoConstr :: PGScalarType -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PGScalarType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PGScalarType
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PGScalarType -> c PGScalarType
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PGScalarType -> c PGScalarType
$cp1Data :: Typeable PGScalarType
Data)
instance NFData PGScalarType
instance Hashable PGScalarType
instance Cacheable PGScalarType
pgScalarTypeToText :: PGScalarType -> Text
pgScalarTypeToText :: PGScalarType -> Text
pgScalarTypeToText = \case
PGScalarType
PGSmallInt -> Text
"smallint"
PGScalarType
PGInteger -> Text
"integer"
PGScalarType
PGBigInt -> Text
"bigint"
PGScalarType
PGSerial -> Text
"serial"
PGScalarType
PGBigSerial -> Text
"bigserial"
PGScalarType
PGFloat -> Text
"real"
PGScalarType
PGDouble -> Text
"float8"
PGScalarType
PGNumeric -> Text
"numeric"
PGScalarType
PGMoney -> Text
"money"
PGScalarType
PGBoolean -> Text
"boolean"
PGScalarType
PGChar -> Text
"bpchar"
PGScalarType
PGVarchar -> Text
"varchar"
PGScalarType
PGText -> Text
"text"
PGScalarType
PGCitext -> Text
"citext"
PGScalarType
PGDate -> Text
"date"
PGScalarType
PGTimeStamp -> Text
"timestamp"
PGScalarType
PGTimeStampTZ -> Text
"timestamptz"
PGScalarType
PGTimeTZ -> Text
"timetz"
PGScalarType
PGJSON -> Text
"json"
PGScalarType
PGJSONB -> Text
"jsonb"
PGScalarType
PGGeometry -> Text
"geometry"
PGScalarType
PGGeography -> Text
"geography"
PGScalarType
PGRaster -> Text
"raster"
PGScalarType
PGUUID -> Text
"uuid"
PGScalarType
PGLtree -> Text
"ltree"
PGScalarType
PGLquery -> Text
"lquery"
PGScalarType
PGLtxtquery -> Text
"ltxtquery"
PGArray PGScalarType
t -> PGScalarType -> Text
pgScalarTypeToText PGScalarType
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"[]"
PGUnknown Text
t -> Text
t
PGCompositeScalar Text
t -> Text
t
PGEnumScalar Text
t -> Text
t
instance ToSQL PGScalarType where
toSQL :: PGScalarType -> Builder
toSQL =
Text -> Builder
TB.text (Text -> Builder)
-> (PGScalarType -> Text) -> PGScalarType -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
PGEnumScalar Text
t -> Text -> Text
pgFmtIdentifier Text
t
PGScalarType
scalarType -> PGScalarType -> Text
pgScalarTypeToText PGScalarType
scalarType
instance ToJSON PGScalarType where
toJSON :: PGScalarType -> Value
toJSON = Text -> Value
String (Text -> Value) -> (PGScalarType -> Text) -> PGScalarType -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PGScalarType -> Text
pgScalarTypeToText
instance ToJSONKey PGScalarType where
toJSONKey :: ToJSONKeyFunction PGScalarType
toJSONKey = (PGScalarType -> Text) -> ToJSONKeyFunction PGScalarType
forall a. (a -> Text) -> ToJSONKeyFunction a
toJSONKeyText PGScalarType -> Text
pgScalarTypeToText
instance ToTxt PGScalarType where
toTxt :: PGScalarType -> Text
toTxt = PGScalarType -> Text
pgScalarTypeToText
instance ToErrorValue PGScalarType where
toErrorValue :: PGScalarType -> ErrorMessage
toErrorValue = Text -> ErrorMessage
ErrorValue.squote (Text -> ErrorMessage)
-> (PGScalarType -> Text) -> PGScalarType -> ErrorMessage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PGScalarType -> Text
pgScalarTypeToText
textToPGScalarType :: Text -> PGScalarType
textToPGScalarType :: Text -> PGScalarType
textToPGScalarType Text
t = PGScalarType -> Maybe PGScalarType -> PGScalarType
forall a. a -> Maybe a -> a
fromMaybe (Text -> PGScalarType
PGUnknown Text
t) (Text -> [(Text, PGScalarType)] -> Maybe PGScalarType
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
t [(Text, PGScalarType)]
pgScalarTranslations)
{-# NOINLINE pgScalarTranslations #-}
pgScalarTranslations :: [(Text, PGScalarType)]
pgScalarTranslations :: [(Text, PGScalarType)]
pgScalarTranslations =
[ (Text
"serial", PGScalarType
PGSerial),
(Text
"bigserial", PGScalarType
PGBigSerial),
(Text
"smallint", PGScalarType
PGSmallInt),
(Text
"int2", PGScalarType
PGSmallInt),
(Text
"integer", PGScalarType
PGInteger),
(Text
"int4", PGScalarType
PGInteger),
(Text
"bigint", PGScalarType
PGBigInt),
(Text
"int8", PGScalarType
PGBigInt),
(Text
"real", PGScalarType
PGFloat),
(Text
"float4", PGScalarType
PGFloat),
(Text
"double precision", PGScalarType
PGDouble),
(Text
"float8", PGScalarType
PGDouble),
(Text
"numeric", PGScalarType
PGNumeric),
(Text
"decimal", PGScalarType
PGNumeric),
(Text
"money", PGScalarType
PGMoney),
(Text
"boolean", PGScalarType
PGBoolean),
(Text
"bool", PGScalarType
PGBoolean),
(Text
"bpchar", PGScalarType
PGChar),
(Text
"char", PGScalarType
PGChar),
(Text
"character", PGScalarType
PGChar),
(Text
"varchar", PGScalarType
PGVarchar),
(Text
"character varying", PGScalarType
PGVarchar),
(Text
"text", PGScalarType
PGText),
(Text
"citext", PGScalarType
PGCitext),
(Text
"date", PGScalarType
PGDate),
(Text
"timestamp", PGScalarType
PGTimeStamp),
(Text
"timestamp without time zone", PGScalarType
PGTimeStamp),
(Text
"timestamptz", PGScalarType
PGTimeStampTZ),
(Text
"timestamp with time zone", PGScalarType
PGTimeStampTZ),
(Text
"timetz", PGScalarType
PGTimeTZ),
(Text
"time with time zone", PGScalarType
PGTimeTZ),
(Text
"json", PGScalarType
PGJSON),
(Text
"jsonb", PGScalarType
PGJSONB),
(Text
"geometry", PGScalarType
PGGeometry),
(Text
"geography", PGScalarType
PGGeography),
(Text
"raster", PGScalarType
PGRaster),
(Text
"uuid", PGScalarType
PGUUID),
(Text
"ltree", PGScalarType
PGLtree),
(Text
"lquery", PGScalarType
PGLquery),
(Text
"ltxtquery", PGScalarType
PGLtxtquery)
]
instance FromJSON PGScalarType where
parseJSON :: Value -> Parser PGScalarType
parseJSON (String Text
t) = PGScalarType -> Parser PGScalarType
forall (m :: * -> *) a. Monad m => a -> m a
return (PGScalarType -> Parser PGScalarType)
-> PGScalarType -> Parser PGScalarType
forall a b. (a -> b) -> a -> b
$ Text -> PGScalarType
textToPGScalarType Text
t
parseJSON (Object Object
o) = do
PGTypeKind
typeType <- Object
o Object -> Key -> Parser PGTypeKind
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Text
typeName <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
PGScalarType -> Parser PGScalarType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PGScalarType -> Parser PGScalarType)
-> PGScalarType -> Parser PGScalarType
forall a b. (a -> b) -> a -> b
$
case PGTypeKind
typeType of
PGTypeKind
PGKindEnum -> Text -> PGScalarType
PGEnumScalar Text
typeName
PGTypeKind
PGKindComposite -> Text -> PGScalarType
PGCompositeScalar Text
typeName
PGTypeKind
_ -> Text -> PGScalarType
textToPGScalarType Text
typeName
parseJSON Value
_ = String -> Parser PGScalarType
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Expecting a string or object for PGScalarType"
isNumType :: PGScalarType -> Bool
isNumType :: PGScalarType -> Bool
isNumType PGScalarType
PGInteger = Bool
True
isNumType PGScalarType
PGSmallInt = Bool
True
isNumType PGScalarType
PGBigInt = Bool
True
isNumType PGScalarType
PGFloat = Bool
True
isNumType PGScalarType
PGDouble = Bool
True
isNumType PGScalarType
PGNumeric = Bool
True
isNumType PGScalarType
PGMoney = Bool
True
isNumType PGScalarType
_ = Bool
False
stringTypes :: [PGScalarType]
stringTypes :: [PGScalarType]
stringTypes = [PGScalarType
PGVarchar, PGScalarType
PGText, PGScalarType
PGCitext, PGScalarType
PGChar]
isStringType :: PGScalarType -> Bool
isStringType :: PGScalarType -> Bool
isStringType = (PGScalarType -> [PGScalarType] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [PGScalarType]
stringTypes)
jsonTypes :: [PGScalarType]
jsonTypes :: [PGScalarType]
jsonTypes = [PGScalarType
PGJSON, PGScalarType
PGJSONB]
isJSONType :: PGScalarType -> Bool
isJSONType :: PGScalarType -> Bool
isJSONType = (PGScalarType -> [PGScalarType] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [PGScalarType]
jsonTypes)
isComparableType :: PGScalarType -> Bool
isComparableType :: PGScalarType -> Bool
isComparableType PGScalarType
PGJSON = Bool
False
isComparableType PGScalarType
PGJSONB = Bool
False
isComparableType PGScalarType
PGGeometry = Bool
False
isComparableType PGScalarType
PGGeography = Bool
False
isComparableType PGScalarType
PGBoolean = Bool
False
isComparableType (PGUnknown Text
_) = Bool
False
isComparableType PGScalarType
_ = Bool
True
isBigNum :: PGScalarType -> Bool
isBigNum :: PGScalarType -> Bool
isBigNum = \case
PGScalarType
PGBigInt -> Bool
True
PGScalarType
PGBigSerial -> Bool
True
PGScalarType
PGNumeric -> Bool
True
PGScalarType
PGDouble -> Bool
True
PGScalarType
PGMoney -> Bool
True
PGScalarType
_ -> Bool
False
geoTypes :: [PGScalarType]
geoTypes :: [PGScalarType]
geoTypes = [PGScalarType
PGGeometry, PGScalarType
PGGeography]
isGeoType :: PGScalarType -> Bool
isGeoType :: PGScalarType -> Bool
isGeoType = (PGScalarType -> [PGScalarType] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [PGScalarType]
geoTypes)
data PGTypeKind
= PGKindBase
| PGKindComposite
| PGKindDomain
| PGKindEnum
| PGKindRange
| PGKindPseudo
| PGKindUnknown Text
deriving (Int -> PGTypeKind -> ShowS
[PGTypeKind] -> ShowS
PGTypeKind -> String
(Int -> PGTypeKind -> ShowS)
-> (PGTypeKind -> String)
-> ([PGTypeKind] -> ShowS)
-> Show PGTypeKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PGTypeKind] -> ShowS
$cshowList :: [PGTypeKind] -> ShowS
show :: PGTypeKind -> String
$cshow :: PGTypeKind -> String
showsPrec :: Int -> PGTypeKind -> ShowS
$cshowsPrec :: Int -> PGTypeKind -> ShowS
Show, PGTypeKind -> PGTypeKind -> Bool
(PGTypeKind -> PGTypeKind -> Bool)
-> (PGTypeKind -> PGTypeKind -> Bool) -> Eq PGTypeKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PGTypeKind -> PGTypeKind -> Bool
$c/= :: PGTypeKind -> PGTypeKind -> Bool
== :: PGTypeKind -> PGTypeKind -> Bool
$c== :: PGTypeKind -> PGTypeKind -> Bool
Eq, (forall x. PGTypeKind -> Rep PGTypeKind x)
-> (forall x. Rep PGTypeKind x -> PGTypeKind) -> Generic PGTypeKind
forall x. Rep PGTypeKind x -> PGTypeKind
forall x. PGTypeKind -> Rep PGTypeKind x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PGTypeKind x -> PGTypeKind
$cfrom :: forall x. PGTypeKind -> Rep PGTypeKind x
Generic)
instance NFData PGTypeKind
instance Hashable PGTypeKind
instance Cacheable PGTypeKind
instance FromJSON PGTypeKind where
parseJSON :: Value -> Parser PGTypeKind
parseJSON = String -> (Text -> Parser PGTypeKind) -> Value -> Parser PGTypeKind
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"postgresTypeKind" ((Text -> Parser PGTypeKind) -> Value -> Parser PGTypeKind)
-> (Text -> Parser PGTypeKind) -> Value -> Parser PGTypeKind
forall a b. (a -> b) -> a -> b
$
\Text
t -> PGTypeKind -> Parser PGTypeKind
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PGTypeKind -> Parser PGTypeKind)
-> PGTypeKind -> Parser PGTypeKind
forall a b. (a -> b) -> a -> b
$ case Text
t of
Text
"b" -> PGTypeKind
PGKindBase
Text
"c" -> PGTypeKind
PGKindComposite
Text
"d" -> PGTypeKind
PGKindDomain
Text
"e" -> PGTypeKind
PGKindEnum
Text
"r" -> PGTypeKind
PGKindRange
Text
"p" -> PGTypeKind
PGKindPseudo
Text
_ -> Text -> PGTypeKind
PGKindUnknown Text
t
instance ToJSON PGTypeKind where
toJSON :: PGTypeKind -> Value
toJSON = \case
PGTypeKind
PGKindBase -> Value
"b"
PGTypeKind
PGKindComposite -> Value
"c"
PGTypeKind
PGKindDomain -> Value
"d"
PGTypeKind
PGKindEnum -> Value
"e"
PGTypeKind
PGKindRange -> Value
"r"
PGTypeKind
PGKindPseudo -> Value
"p"
PGKindUnknown Text
t -> Text -> Value
String Text
t
data QualifiedPGType = QualifiedPGType
{ QualifiedPGType -> SchemaName
_qptSchema :: SchemaName,
QualifiedPGType -> PGScalarType
_qptName :: PGScalarType,
QualifiedPGType -> PGTypeKind
_qptType :: PGTypeKind
}
deriving (Int -> QualifiedPGType -> ShowS
[QualifiedPGType] -> ShowS
QualifiedPGType -> String
(Int -> QualifiedPGType -> ShowS)
-> (QualifiedPGType -> String)
-> ([QualifiedPGType] -> ShowS)
-> Show QualifiedPGType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QualifiedPGType] -> ShowS
$cshowList :: [QualifiedPGType] -> ShowS
show :: QualifiedPGType -> String
$cshow :: QualifiedPGType -> String
showsPrec :: Int -> QualifiedPGType -> ShowS
$cshowsPrec :: Int -> QualifiedPGType -> ShowS
Show, QualifiedPGType -> QualifiedPGType -> Bool
(QualifiedPGType -> QualifiedPGType -> Bool)
-> (QualifiedPGType -> QualifiedPGType -> Bool)
-> Eq QualifiedPGType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QualifiedPGType -> QualifiedPGType -> Bool
$c/= :: QualifiedPGType -> QualifiedPGType -> Bool
== :: QualifiedPGType -> QualifiedPGType -> Bool
$c== :: QualifiedPGType -> QualifiedPGType -> Bool
Eq, (forall x. QualifiedPGType -> Rep QualifiedPGType x)
-> (forall x. Rep QualifiedPGType x -> QualifiedPGType)
-> Generic QualifiedPGType
forall x. Rep QualifiedPGType x -> QualifiedPGType
forall x. QualifiedPGType -> Rep QualifiedPGType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep QualifiedPGType x -> QualifiedPGType
$cfrom :: forall x. QualifiedPGType -> Rep QualifiedPGType x
Generic)
instance NFData QualifiedPGType
instance Hashable QualifiedPGType
instance Cacheable QualifiedPGType
$(deriveJSON hasuraJSON ''QualifiedPGType)
isBaseType :: QualifiedPGType -> Bool
isBaseType :: QualifiedPGType -> Bool
isBaseType (QualifiedPGType SchemaName
_ PGScalarType
n PGTypeKind
ty) =
Bool
notUnknown Bool -> Bool -> Bool
&& (PGTypeKind
ty PGTypeKind -> PGTypeKind -> Bool
forall a. Eq a => a -> a -> Bool
== PGTypeKind
PGKindBase)
where
notUnknown :: Bool
notUnknown = case PGScalarType
n of
PGUnknown Text
_ -> Bool
False
PGScalarType
_ -> Bool
True
typeToTable :: QualifiedPGType -> QualifiedTable
typeToTable :: QualifiedPGType -> QualifiedTable
typeToTable (QualifiedPGType SchemaName
sch PGScalarType
n PGTypeKind
_) =
SchemaName -> TableName -> QualifiedTable
forall a. SchemaName -> a -> QualifiedObject a
QualifiedObject SchemaName
sch (TableName -> QualifiedTable) -> TableName -> QualifiedTable
forall a b. (a -> b) -> a -> b
$ Text -> TableName
TableName (Text -> TableName) -> Text -> TableName
forall a b. (a -> b) -> a -> b
$ PGScalarType -> Text
pgScalarTypeToText PGScalarType
n
mkFunctionArgScalarType :: QualifiedPGType -> PGScalarType
mkFunctionArgScalarType :: QualifiedPGType -> PGScalarType
mkFunctionArgScalarType (QualifiedPGType SchemaName
_schema PGScalarType
name PGTypeKind
type') =
case PGTypeKind
type' of
PGTypeKind
PGKindComposite -> Text -> PGScalarType
PGCompositeScalar (Text -> PGScalarType) -> Text -> PGScalarType
forall a b. (a -> b) -> a -> b
$ PGScalarType -> Text
forall a. ToTxt a => a -> Text
toTxt PGScalarType
name
PGTypeKind
_ -> PGScalarType
name
data PGRawFunctionInfo = PGRawFunctionInfo
{ PGRawFunctionInfo -> OID
rfiOid :: OID,
PGRawFunctionInfo -> Bool
rfiHasVariadic :: Bool,
PGRawFunctionInfo -> FunctionVolatility
rfiFunctionType :: FunctionVolatility,
PGRawFunctionInfo -> SchemaName
rfiReturnTypeSchema :: SchemaName,
PGRawFunctionInfo -> PGScalarType
rfiReturnTypeName :: PGScalarType,
PGRawFunctionInfo -> PGTypeKind
rfiReturnTypeType :: PGTypeKind,
PGRawFunctionInfo -> Bool
rfiReturnsSet :: Bool,
PGRawFunctionInfo -> [QualifiedPGType]
rfiInputArgTypes :: [QualifiedPGType],
PGRawFunctionInfo -> [FunctionArgName]
rfiInputArgNames :: [FunctionArgName],
PGRawFunctionInfo -> Int
rfiDefaultArgs :: Int,
PGRawFunctionInfo -> Bool
rfiReturnsTable :: Bool,
PGRawFunctionInfo -> Maybe PGDescription
rfiDescription :: Maybe PGDescription
}
deriving (Int -> PGRawFunctionInfo -> ShowS
[PGRawFunctionInfo] -> ShowS
PGRawFunctionInfo -> String
(Int -> PGRawFunctionInfo -> ShowS)
-> (PGRawFunctionInfo -> String)
-> ([PGRawFunctionInfo] -> ShowS)
-> Show PGRawFunctionInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PGRawFunctionInfo] -> ShowS
$cshowList :: [PGRawFunctionInfo] -> ShowS
show :: PGRawFunctionInfo -> String
$cshow :: PGRawFunctionInfo -> String
showsPrec :: Int -> PGRawFunctionInfo -> ShowS
$cshowsPrec :: Int -> PGRawFunctionInfo -> ShowS
Show, PGRawFunctionInfo -> PGRawFunctionInfo -> Bool
(PGRawFunctionInfo -> PGRawFunctionInfo -> Bool)
-> (PGRawFunctionInfo -> PGRawFunctionInfo -> Bool)
-> Eq PGRawFunctionInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PGRawFunctionInfo -> PGRawFunctionInfo -> Bool
$c/= :: PGRawFunctionInfo -> PGRawFunctionInfo -> Bool
== :: PGRawFunctionInfo -> PGRawFunctionInfo -> Bool
$c== :: PGRawFunctionInfo -> PGRawFunctionInfo -> Bool
Eq, (forall x. PGRawFunctionInfo -> Rep PGRawFunctionInfo x)
-> (forall x. Rep PGRawFunctionInfo x -> PGRawFunctionInfo)
-> Generic PGRawFunctionInfo
forall x. Rep PGRawFunctionInfo x -> PGRawFunctionInfo
forall x. PGRawFunctionInfo -> Rep PGRawFunctionInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PGRawFunctionInfo x -> PGRawFunctionInfo
$cfrom :: forall x. PGRawFunctionInfo -> Rep PGRawFunctionInfo x
Generic)
instance NFData PGRawFunctionInfo
instance Cacheable PGRawFunctionInfo
$(deriveJSON hasuraJSON ''PGRawFunctionInfo)
mkScalarTypeName :: MonadError QErr m => PGScalarType -> m G.Name
mkScalarTypeName :: PGScalarType -> m Name
mkScalarTypeName PGScalarType
PGInteger = Name -> m Name
forall (f :: * -> *) a. Applicative f => a -> f a
pure Name
GName._Int
mkScalarTypeName PGScalarType
PGBoolean = Name -> m Name
forall (f :: * -> *) a. Applicative f => a -> f a
pure Name
GName._Boolean
mkScalarTypeName PGScalarType
PGFloat = Name -> m Name
forall (f :: * -> *) a. Applicative f => a -> f a
pure Name
GName._Float
mkScalarTypeName PGScalarType
PGText = Name -> m Name
forall (f :: * -> *) a. Applicative f => a -> f a
pure Name
GName._String
mkScalarTypeName PGScalarType
PGVarchar = Name -> m Name
forall (f :: * -> *) a. Applicative f => a -> f a
pure Name
GName._String
mkScalarTypeName (PGCompositeScalar Text
compositeScalarType) =
(Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name.__scalar) (Name -> Name) -> m Name -> m Name
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe Name
G.mkName Text
compositeScalarType
Maybe Name -> m Name -> m Name
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` Code -> Text -> m Name
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400
Code
ValidationFailed
( Text
"cannot use SQL type " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
compositeScalarType Text -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" in the GraphQL schema because its name is not a "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"valid GraphQL identifier"
)
mkScalarTypeName PGScalarType
scalarType =
Text -> Maybe Name
G.mkName (PGScalarType -> Text
pgScalarTypeToText PGScalarType
scalarType)
Maybe Name -> m Name -> m Name
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` Code -> Text -> m Name
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400
Code
ValidationFailed
( Text
"cannot use SQL type " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> PGScalarType
scalarType PGScalarType -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" in the GraphQL schema because its name is not a "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"valid GraphQL identifier"
)
instance IsIdentifier RelName where
toIdentifier :: RelName -> Identifier
toIdentifier RelName
rn = Text -> Identifier
Identifier (Text -> Identifier) -> Text -> Identifier
forall a b. (a -> b) -> a -> b
$ RelName -> Text
relNameToTxt RelName
rn
instance IsIdentifier FieldName where
toIdentifier :: FieldName -> Identifier
toIdentifier (FieldName Text
f) = Text -> Identifier
Identifier Text
f
pgTypeOid :: PGScalarType -> PQ.Oid
pgTypeOid :: PGScalarType -> Oid
pgTypeOid = \case
PGScalarType
PGSmallInt -> Oid
PTI.int2
PGScalarType
PGInteger -> Oid
PTI.int4
PGScalarType
PGBigInt -> Oid
PTI.int8
PGScalarType
PGSerial -> Oid
PTI.int4
PGScalarType
PGBigSerial -> Oid
PTI.int8
PGScalarType
PGFloat -> Oid
PTI.float4
PGScalarType
PGDouble -> Oid
PTI.float8
PGScalarType
PGNumeric -> Oid
PTI.numeric
PGScalarType
PGMoney -> Oid
PTI.numeric
PGScalarType
PGBoolean -> Oid
PTI.bool
PGScalarType
PGChar -> Oid
PTI.char
PGScalarType
PGVarchar -> Oid
PTI.varchar
PGScalarType
PGText -> Oid
PTI.text
PGScalarType
PGCitext -> Oid
PTI.text
PGScalarType
PGDate -> Oid
PTI.date
PGScalarType
PGTimeStamp -> Oid
PTI.timestamp
PGScalarType
PGTimeStampTZ -> Oid
PTI.timestamptz
PGScalarType
PGTimeTZ -> Oid
PTI.timetz
PGScalarType
PGJSON -> Oid
PTI.json
PGScalarType
PGJSONB -> Oid
PTI.jsonb
PGScalarType
PGGeometry -> Oid
PTI.text
PGScalarType
PGGeography -> Oid
PTI.text
PGScalarType
PGRaster -> Oid
PTI.text
PGScalarType
PGUUID -> Oid
PTI.uuid
PGScalarType
PGLtree -> Oid
PTI.text
PGScalarType
PGLquery -> Oid
PTI.text
PGScalarType
PGLtxtquery -> Oid
PTI.text
PGUnknown Text
_ -> Oid
PTI.auto
PGCompositeScalar Text
_ -> Oid
PTI.auto
PGEnumScalar Text
_ -> Oid
PTI.auto
PGArray PGScalarType
_ -> Oid
PTI.auto