{-# LANGUAGE TemplateHaskell #-}
module Hasura.SQL.Types
( ToSQL (..),
toSQLTxt,
CollectableType (..),
ExtensionsSchema (..),
)
where
import Autodocodec (Autodocodec (..), HasCodec (codec), dimapCodec, named, textCodec)
import Data.Aeson
import Data.Aeson.TH
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
import Text.Builder qualified as TB
class ToSQL a where
toSQL :: a -> TB.Builder
instance ToSQL TB.Builder where
toSQL :: Builder -> Builder
toSQL Builder
x = Builder
x
instance (ToSQL a) => ToSQL (Maybe a) where
toSQL :: Maybe a -> Builder
toSQL (Just a
a) = a -> Builder
forall a. ToSQL a => a -> Builder
toSQL a
a
toSQL Maybe a
Nothing = Builder
forall a. Monoid a => a
mempty
toSQLTxt :: (ToSQL a) => a -> Text
toSQLTxt :: a -> Text
toSQLTxt = Builder -> Text
TB.run (Builder -> Text) -> (a -> Builder) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Builder
forall a. ToSQL a => a -> Builder
toSQL
data CollectableType a
= CollectableTypeScalar !a
| CollectableTypeArray !a
deriving (Int -> CollectableType a -> ShowS
[CollectableType a] -> ShowS
CollectableType a -> String
(Int -> CollectableType a -> ShowS)
-> (CollectableType a -> String)
-> ([CollectableType a] -> ShowS)
-> Show (CollectableType a)
forall a. Show a => Int -> CollectableType a -> ShowS
forall a. Show a => [CollectableType a] -> ShowS
forall a. Show a => CollectableType a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CollectableType a] -> ShowS
$cshowList :: forall a. Show a => [CollectableType a] -> ShowS
show :: CollectableType a -> String
$cshow :: forall a. Show a => CollectableType a -> String
showsPrec :: Int -> CollectableType a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CollectableType a -> ShowS
Show, CollectableType a -> CollectableType a -> Bool
(CollectableType a -> CollectableType a -> Bool)
-> (CollectableType a -> CollectableType a -> Bool)
-> Eq (CollectableType a)
forall a. Eq a => CollectableType a -> CollectableType a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CollectableType a -> CollectableType a -> Bool
$c/= :: forall a. Eq a => CollectableType a -> CollectableType a -> Bool
== :: CollectableType a -> CollectableType a -> Bool
$c== :: forall a. Eq a => CollectableType a -> CollectableType a -> Bool
Eq, (forall x. CollectableType a -> Rep (CollectableType a) x)
-> (forall x. Rep (CollectableType a) x -> CollectableType a)
-> Generic (CollectableType a)
forall x. Rep (CollectableType a) x -> CollectableType a
forall x. CollectableType a -> Rep (CollectableType a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CollectableType a) x -> CollectableType a
forall a x. CollectableType a -> Rep (CollectableType a) x
$cto :: forall a x. Rep (CollectableType a) x -> CollectableType a
$cfrom :: forall a x. CollectableType a -> Rep (CollectableType a) x
Generic, Typeable (CollectableType a)
DataType
Constr
Typeable (CollectableType a)
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CollectableType a
-> c (CollectableType a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CollectableType a))
-> (CollectableType a -> Constr)
-> (CollectableType a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CollectableType a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CollectableType a)))
-> ((forall b. Data b => b -> b)
-> CollectableType a -> CollectableType a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CollectableType a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CollectableType a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CollectableType a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CollectableType a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CollectableType a -> m (CollectableType a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CollectableType a -> m (CollectableType a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CollectableType a -> m (CollectableType a))
-> Data (CollectableType a)
CollectableType a -> DataType
CollectableType a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CollectableType a))
(forall b. Data b => b -> b)
-> CollectableType a -> CollectableType a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CollectableType a
-> c (CollectableType a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CollectableType a)
forall a. Data a => Typeable (CollectableType a)
forall a. Data a => CollectableType a -> DataType
forall a. Data a => CollectableType a -> Constr
forall a.
Data a =>
(forall b. Data b => b -> b)
-> CollectableType a -> CollectableType a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CollectableType a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CollectableType a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CollectableType a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CollectableType a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CollectableType a -> m (CollectableType a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CollectableType a -> m (CollectableType a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CollectableType a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CollectableType a
-> c (CollectableType a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CollectableType a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CollectableType 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) -> CollectableType a -> u
forall u. (forall d. Data d => d -> u) -> CollectableType a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CollectableType a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CollectableType a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CollectableType a -> m (CollectableType a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CollectableType a -> m (CollectableType a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CollectableType a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CollectableType a
-> c (CollectableType a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CollectableType a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CollectableType a))
$cCollectableTypeArray :: Constr
$cCollectableTypeScalar :: Constr
$tCollectableType :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> CollectableType a -> m (CollectableType a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CollectableType a -> m (CollectableType a)
gmapMp :: (forall d. Data d => d -> m d)
-> CollectableType a -> m (CollectableType a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CollectableType a -> m (CollectableType a)
gmapM :: (forall d. Data d => d -> m d)
-> CollectableType a -> m (CollectableType a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CollectableType a -> m (CollectableType a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> CollectableType a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CollectableType a -> u
gmapQ :: (forall d. Data d => d -> u) -> CollectableType a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CollectableType a -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CollectableType a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CollectableType a -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CollectableType a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CollectableType a -> r
gmapT :: (forall b. Data b => b -> b)
-> CollectableType a -> CollectableType a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CollectableType a -> CollectableType a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CollectableType a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CollectableType a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CollectableType a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CollectableType a))
dataTypeOf :: CollectableType a -> DataType
$cdataTypeOf :: forall a. Data a => CollectableType a -> DataType
toConstr :: CollectableType a -> Constr
$ctoConstr :: forall a. Data a => CollectableType a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CollectableType a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CollectableType a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CollectableType a
-> c (CollectableType a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CollectableType a
-> c (CollectableType a)
$cp1Data :: forall a. Data a => Typeable (CollectableType a)
Data, a -> CollectableType b -> CollectableType a
(a -> b) -> CollectableType a -> CollectableType b
(forall a b. (a -> b) -> CollectableType a -> CollectableType b)
-> (forall a b. a -> CollectableType b -> CollectableType a)
-> Functor CollectableType
forall a b. a -> CollectableType b -> CollectableType a
forall a b. (a -> b) -> CollectableType a -> CollectableType b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> CollectableType b -> CollectableType a
$c<$ :: forall a b. a -> CollectableType b -> CollectableType a
fmap :: (a -> b) -> CollectableType a -> CollectableType b
$cfmap :: forall a b. (a -> b) -> CollectableType a -> CollectableType b
Functor)
instance (NFData a) => NFData (CollectableType a)
instance (Hashable a) => Hashable (CollectableType a)
instance (Cacheable a) => Cacheable (CollectableType a)
$(deriveJSON defaultOptions {constructorTagModifier = drop 6} ''CollectableType)
instance (ToSQL a) => ToSQL (CollectableType a) where
toSQL :: CollectableType a -> Builder
toSQL = \case
CollectableTypeScalar a
ty -> a -> Builder
forall a. ToSQL a => a -> Builder
toSQL a
ty
CollectableTypeArray a
ty -> a -> Builder
forall a. ToSQL a => a -> Builder
toSQL a
ty Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
" array"
newtype ExtensionsSchema = ExtensionsSchema {ExtensionsSchema -> Text
_unExtensionsSchema :: Text}
deriving (Int -> ExtensionsSchema -> ShowS
[ExtensionsSchema] -> ShowS
ExtensionsSchema -> String
(Int -> ExtensionsSchema -> ShowS)
-> (ExtensionsSchema -> String)
-> ([ExtensionsSchema] -> ShowS)
-> Show ExtensionsSchema
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExtensionsSchema] -> ShowS
$cshowList :: [ExtensionsSchema] -> ShowS
show :: ExtensionsSchema -> String
$cshow :: ExtensionsSchema -> String
showsPrec :: Int -> ExtensionsSchema -> ShowS
$cshowsPrec :: Int -> ExtensionsSchema -> ShowS
Show, ExtensionsSchema -> ExtensionsSchema -> Bool
(ExtensionsSchema -> ExtensionsSchema -> Bool)
-> (ExtensionsSchema -> ExtensionsSchema -> Bool)
-> Eq ExtensionsSchema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExtensionsSchema -> ExtensionsSchema -> Bool
$c/= :: ExtensionsSchema -> ExtensionsSchema -> Bool
== :: ExtensionsSchema -> ExtensionsSchema -> Bool
$c== :: ExtensionsSchema -> ExtensionsSchema -> Bool
Eq, Int -> ExtensionsSchema -> Int
ExtensionsSchema -> Int
(Int -> ExtensionsSchema -> Int)
-> (ExtensionsSchema -> Int) -> Hashable ExtensionsSchema
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ExtensionsSchema -> Int
$chash :: ExtensionsSchema -> Int
hashWithSalt :: Int -> ExtensionsSchema -> Int
$chashWithSalt :: Int -> ExtensionsSchema -> Int
Hashable, Eq ExtensionsSchema
Eq ExtensionsSchema
-> (Accesses -> ExtensionsSchema -> ExtensionsSchema -> Bool)
-> Cacheable ExtensionsSchema
Accesses -> ExtensionsSchema -> ExtensionsSchema -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> ExtensionsSchema -> ExtensionsSchema -> Bool
$cunchanged :: Accesses -> ExtensionsSchema -> ExtensionsSchema -> Bool
$cp1Cacheable :: Eq ExtensionsSchema
Cacheable, ExtensionsSchema -> ()
(ExtensionsSchema -> ()) -> NFData ExtensionsSchema
forall a. (a -> ()) -> NFData a
rnf :: ExtensionsSchema -> ()
$crnf :: ExtensionsSchema -> ()
NFData)
deriving (Value -> Parser [ExtensionsSchema]
Value -> Parser ExtensionsSchema
(Value -> Parser ExtensionsSchema)
-> (Value -> Parser [ExtensionsSchema])
-> FromJSON ExtensionsSchema
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ExtensionsSchema]
$cparseJSONList :: Value -> Parser [ExtensionsSchema]
parseJSON :: Value -> Parser ExtensionsSchema
$cparseJSON :: Value -> Parser ExtensionsSchema
FromJSON, [ExtensionsSchema] -> Value
[ExtensionsSchema] -> Encoding
ExtensionsSchema -> Value
ExtensionsSchema -> Encoding
(ExtensionsSchema -> Value)
-> (ExtensionsSchema -> Encoding)
-> ([ExtensionsSchema] -> Value)
-> ([ExtensionsSchema] -> Encoding)
-> ToJSON ExtensionsSchema
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ExtensionsSchema] -> Encoding
$ctoEncodingList :: [ExtensionsSchema] -> Encoding
toJSONList :: [ExtensionsSchema] -> Value
$ctoJSONList :: [ExtensionsSchema] -> Value
toEncoding :: ExtensionsSchema -> Encoding
$ctoEncoding :: ExtensionsSchema -> Encoding
toJSON :: ExtensionsSchema -> Value
$ctoJSON :: ExtensionsSchema -> Value
ToJSON) via (Autodocodec ExtensionsSchema)
instance HasCodec ExtensionsSchema where
codec :: JSONCodec ExtensionsSchema
codec = Text -> JSONCodec ExtensionsSchema -> JSONCodec ExtensionsSchema
forall input output.
Text -> ValueCodec input output -> ValueCodec input output
named Text
"ExtensionsSchema" (JSONCodec ExtensionsSchema -> JSONCodec ExtensionsSchema)
-> JSONCodec ExtensionsSchema -> JSONCodec ExtensionsSchema
forall a b. (a -> b) -> a -> b
$ (Text -> ExtensionsSchema)
-> (ExtensionsSchema -> Text)
-> Codec Value Text Text
-> JSONCodec ExtensionsSchema
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> ExtensionsSchema
ExtensionsSchema ExtensionsSchema -> Text
_unExtensionsSchema Codec Value Text Text
textCodec