2022-03-31 07:45:03 +03:00
|
|
|
{-# LANGUAGE DeriveAnyClass #-}
|
|
|
|
{-# LANGUAGE OverloadedLists #-}
|
|
|
|
{-# LANGUAGE StandaloneDeriving #-}
|
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
|
2022-03-16 07:12:15 +03:00
|
|
|
--
|
|
|
|
module Hasura.Backends.DataWrapper.API.V0.Query
|
|
|
|
( Query (..),
|
|
|
|
Field (..),
|
2022-03-31 07:45:03 +03:00
|
|
|
RelField (..),
|
2022-03-16 07:12:15 +03:00
|
|
|
ForeignKey (..),
|
|
|
|
PrimaryKey (..),
|
2022-04-01 04:20:23 +03:00
|
|
|
QueryResponse (..),
|
2022-03-16 07:12:15 +03:00
|
|
|
)
|
|
|
|
where
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
2022-03-31 07:45:03 +03:00
|
|
|
import Autodocodec.Extended
|
|
|
|
import Autodocodec.OpenAPI ()
|
2022-04-01 04:20:23 +03:00
|
|
|
import Control.DeepSeq (NFData)
|
2022-03-31 07:45:03 +03:00
|
|
|
import Control.Lens.TH (makePrisms)
|
2022-04-01 04:20:23 +03:00
|
|
|
import Data.Aeson (FromJSON, FromJSONKey, Object, ToJSON, ToJSONKey)
|
|
|
|
import Data.Data (Data)
|
2022-03-16 07:12:15 +03:00
|
|
|
import Data.HashMap.Strict qualified as M
|
2022-04-01 04:20:23 +03:00
|
|
|
import Data.Hashable (Hashable)
|
|
|
|
import Data.List.NonEmpty (NonEmpty)
|
2022-03-31 07:45:03 +03:00
|
|
|
import Data.OpenApi (ToSchema)
|
2022-04-01 04:20:23 +03:00
|
|
|
import Data.Text (Text)
|
|
|
|
import GHC.Generics (Generic)
|
2022-03-16 07:12:15 +03:00
|
|
|
import Hasura.Backends.DataWrapper.API.V0.Column qualified as API.V0
|
|
|
|
import Hasura.Backends.DataWrapper.API.V0.Expression qualified as API.V0
|
|
|
|
import Hasura.Backends.DataWrapper.API.V0.OrderBy qualified as API.V0
|
|
|
|
import Hasura.Backends.DataWrapper.API.V0.Table qualified as API.V0
|
2022-04-01 04:20:23 +03:00
|
|
|
import Prelude
|
2022-03-16 07:12:15 +03:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
-- | A serializable request to retrieve strutured data from some
|
|
|
|
-- source.
|
|
|
|
data Query = Query
|
|
|
|
{ fields :: M.HashMap Text Field,
|
|
|
|
from :: API.V0.TableName,
|
|
|
|
limit :: Maybe Int,
|
|
|
|
offset :: Maybe Int,
|
|
|
|
where_ :: Maybe API.V0.Expression,
|
2022-03-31 07:45:03 +03:00
|
|
|
orderBy :: Maybe (NonEmpty API.V0.OrderBy)
|
2022-03-16 07:12:15 +03:00
|
|
|
}
|
|
|
|
deriving stock (Eq, Ord, Show, Generic, Data)
|
2022-03-31 07:45:03 +03:00
|
|
|
deriving (FromJSON, ToJSON, ToSchema) via Autodocodec Query
|
|
|
|
|
|
|
|
instance HasCodec Query where
|
|
|
|
codec =
|
|
|
|
-- named "query" $
|
|
|
|
object "Query" $
|
|
|
|
Query
|
|
|
|
<$> requiredField "fields" "Fields of the query" .= fields
|
|
|
|
<*> requiredField "from" "Source table" .= from
|
|
|
|
<*> optionalFieldOrNull "limit" "Optionally limit to N results" .= limit
|
|
|
|
<*> optionalFieldOrNull "offset" "Optionally offset from the Nth result" .= offset
|
|
|
|
<*> optionalFieldOrNull "where" "Optionally constrain the results to satisfy some predicate" .= where_
|
|
|
|
<*> optionalFieldOrNull "order_by" "Optionally order the results by the value of one or more fields" .= orderBy
|
2022-03-16 07:12:15 +03:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
2022-03-31 07:45:03 +03:00
|
|
|
data RelField = RelField
|
|
|
|
{ fieldMapping :: M.HashMap PrimaryKey ForeignKey,
|
|
|
|
query :: Query
|
|
|
|
}
|
2022-03-16 07:12:15 +03:00
|
|
|
deriving stock (Eq, Ord, Show, Generic, Data)
|
|
|
|
|
2022-03-31 07:45:03 +03:00
|
|
|
instance HasObjectCodec RelField where
|
|
|
|
objectCodec =
|
|
|
|
RelField
|
|
|
|
<$> requiredField "field_mapping" "Mapping from local fields to remote fields" .= fieldMapping
|
|
|
|
<*> requiredField "query" "Relationship query" .= query
|
|
|
|
|
2022-03-16 07:12:15 +03:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
2022-03-31 07:45:03 +03:00
|
|
|
newtype PrimaryKey = PrimaryKey {unPrimaryKey :: API.V0.ColumnName}
|
2022-03-16 07:12:15 +03:00
|
|
|
deriving stock (Data, Generic)
|
2022-03-31 07:45:03 +03:00
|
|
|
deriving newtype (Eq, Hashable, Ord, Show, ToJSONKey, FromJSONKey)
|
|
|
|
deriving (FromJSON, ToJSON, ToSchema) via Autodocodec PrimaryKey
|
|
|
|
|
|
|
|
instance HasCodec PrimaryKey where
|
|
|
|
codec = dimapCodec PrimaryKey unPrimaryKey codec
|
2022-03-16 07:12:15 +03:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
2022-03-31 07:45:03 +03:00
|
|
|
newtype ForeignKey = ForeignKey {unForeignKey :: API.V0.ColumnName}
|
2022-03-16 07:12:15 +03:00
|
|
|
deriving stock (Data, Generic)
|
2022-03-31 07:45:03 +03:00
|
|
|
deriving newtype (Eq, Hashable, Ord, Show)
|
|
|
|
deriving (FromJSON, ToJSON, ToSchema) via Autodocodec ForeignKey
|
|
|
|
|
|
|
|
instance HasCodec ForeignKey where
|
|
|
|
codec = dimapCodec ForeignKey unForeignKey codec
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
-- | A serializable field targeted by a 'Query'.
|
|
|
|
data Field
|
|
|
|
= ColumnField (ValueWrapper "column" API.V0.ColumnName)
|
|
|
|
| RelationshipField RelField
|
|
|
|
deriving stock (Eq, Ord, Show, Generic, Data)
|
|
|
|
|
|
|
|
$(makePrisms ''Field)
|
|
|
|
|
|
|
|
instance HasCodec Field where
|
|
|
|
codec =
|
|
|
|
named "Field" $
|
|
|
|
sumTypeCodec
|
|
|
|
[ TypeAlternative "ColumnField" "column" _ColumnField,
|
|
|
|
TypeAlternative "RelationshipField" "relationship" _RelationshipField
|
|
|
|
]
|
|
|
|
|
|
|
|
deriving via Autodocodec Field instance FromJSON Field
|
|
|
|
|
|
|
|
deriving via Autodocodec Field instance ToJSON Field
|
|
|
|
|
|
|
|
deriving via Autodocodec Field instance ToSchema Field
|
2022-04-01 04:20:23 +03:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Query Response
|
|
|
|
|
|
|
|
-- | The resolved query response provided by the 'POST /query'
|
|
|
|
-- endpoint encoded as 'J.Value'.
|
|
|
|
newtype QueryResponse = QueryResponse {getQueryResponse :: [Object]}
|
|
|
|
deriving newtype (Eq, Ord, Show, NFData)
|
|
|
|
deriving (ToJSON, FromJSON, ToSchema) via Autodocodec [Object]
|