{-# LANGUAGE DuplicateRecordFields #-}

module Hasura.Backends.BigQuery.Meta
  ( MetadataError (..),
    getTables,
    RestTableReference (..),
    RestTable (..),
    RestTableSchema (..),
    RestFieldSchema (..),
    RestType (..),
    Mode (..),
    RestRoutineType (..),
    RestArgument (..),
    RestStandardSqlField (..),
    RestStandardSqlTableType (..),
    RestRoutineReference (..),
    routineReferenceToFunctionName,
    RestRoutine (..),
    getRoutines,
  )
where

import Control.Exception.Safe
import Control.Monad.IO.Class
import Control.Monad.Trans.Except
import Data.Aeson
import Data.Aeson qualified as J
import Data.Foldable
import Data.Maybe
import Data.Sequence qualified as Seq
import Data.Text qualified as T
import GHC.Generics
import Hasura.Backends.BigQuery.Connection
import Hasura.Backends.BigQuery.Source
import Hasura.Backends.BigQuery.Types
import Hasura.Prelude
import Network.HTTP.Simple
import Network.HTTP.Types

--------------------------------------------------------------------------------
-- Types

data MetadataError
  = RestProblem RestProblem
  deriving (Int -> MetadataError -> ShowS
[MetadataError] -> ShowS
MetadataError -> String
(Int -> MetadataError -> ShowS)
-> (MetadataError -> String)
-> ([MetadataError] -> ShowS)
-> Show MetadataError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MetadataError -> ShowS
showsPrec :: Int -> MetadataError -> ShowS
$cshow :: MetadataError -> String
show :: MetadataError -> String
$cshowList :: [MetadataError] -> ShowS
showList :: [MetadataError] -> ShowS
Show)

data RestProblem
  = GetTablesProblem SomeException
  | GetTableProblem SomeException
  | GetRoutineProblem SomeException
  | GetMetaDecodeProblem String
  | GetTablesBigQueryProblem BigQueryProblem
  | GetRoutinesBigQueryProblem BigQueryProblem
  | RESTRequestNonOK Status
  deriving (Int -> RestProblem -> ShowS
[RestProblem] -> ShowS
RestProblem -> String
(Int -> RestProblem -> ShowS)
-> (RestProblem -> String)
-> ([RestProblem] -> ShowS)
-> Show RestProblem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestProblem -> ShowS
showsPrec :: Int -> RestProblem -> ShowS
$cshow :: RestProblem -> String
show :: RestProblem -> String
$cshowList :: [RestProblem] -> ShowS
showList :: [RestProblem] -> ShowS
Show)

data RestTableList = RestTableList
  { RestTableList -> Maybe Text
nextPageToken :: Maybe Text,
    RestTableList -> [RestTableBrief]
tables :: [RestTableBrief]
  }
  deriving (Int -> RestTableList -> ShowS
[RestTableList] -> ShowS
RestTableList -> String
(Int -> RestTableList -> ShowS)
-> (RestTableList -> String)
-> ([RestTableList] -> ShowS)
-> Show RestTableList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestTableList -> ShowS
showsPrec :: Int -> RestTableList -> ShowS
$cshow :: RestTableList -> String
show :: RestTableList -> String
$cshowList :: [RestTableList] -> ShowS
showList :: [RestTableList] -> ShowS
Show)

instance FromJSON RestTableList where
  parseJSON :: Value -> Parser RestTableList
parseJSON =
    String
-> (Object -> Parser RestTableList)
-> Value
-> Parser RestTableList
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject
      String
"RestTableList"
      ( \Object
o -> do
          Text
kind <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"kind"
          case Text
kind of
            (Text
"bigquery#tableList" :: Text) -> do
              Maybe Text
nextPageToken <- Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"nextPageToken"
              [RestTableBrief]
tables <- Object
o Object -> Key -> Parser (Maybe [RestTableBrief])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"tables" Parser (Maybe [RestTableBrief])
-> [RestTableBrief] -> Parser [RestTableBrief]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
              RestTableList -> Parser RestTableList
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestTableList {[RestTableBrief]
Maybe Text
$sel:nextPageToken:RestTableList :: Maybe Text
$sel:tables:RestTableList :: [RestTableBrief]
nextPageToken :: Maybe Text
tables :: [RestTableBrief]
..}
            Text
_ -> String -> Parser RestTableList
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Expected kind of bigquery#tableList"
      )

data RestTableBrief = RestTableBrief
  { RestTableBrief -> RestTableReference
tableReference :: RestTableReference
  }
  deriving (Int -> RestTableBrief -> ShowS
[RestTableBrief] -> ShowS
RestTableBrief -> String
(Int -> RestTableBrief -> ShowS)
-> (RestTableBrief -> String)
-> ([RestTableBrief] -> ShowS)
-> Show RestTableBrief
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestTableBrief -> ShowS
showsPrec :: Int -> RestTableBrief -> ShowS
$cshow :: RestTableBrief -> String
show :: RestTableBrief -> String
$cshowList :: [RestTableBrief] -> ShowS
showList :: [RestTableBrief] -> ShowS
Show, (forall x. RestTableBrief -> Rep RestTableBrief x)
-> (forall x. Rep RestTableBrief x -> RestTableBrief)
-> Generic RestTableBrief
forall x. Rep RestTableBrief x -> RestTableBrief
forall x. RestTableBrief -> Rep RestTableBrief x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RestTableBrief -> Rep RestTableBrief x
from :: forall x. RestTableBrief -> Rep RestTableBrief x
$cto :: forall x. Rep RestTableBrief x -> RestTableBrief
to :: forall x. Rep RestTableBrief x -> RestTableBrief
Generic)

instance FromJSON RestTableBrief

data RestTableReference = RestTableReference
  { RestTableReference -> Text
datasetId :: Text,
    RestTableReference -> Text
projectId :: Text,
    RestTableReference -> Text
tableId :: Text
  }
  deriving (Int -> RestTableReference -> ShowS
[RestTableReference] -> ShowS
RestTableReference -> String
(Int -> RestTableReference -> ShowS)
-> (RestTableReference -> String)
-> ([RestTableReference] -> ShowS)
-> Show RestTableReference
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestTableReference -> ShowS
showsPrec :: Int -> RestTableReference -> ShowS
$cshow :: RestTableReference -> String
show :: RestTableReference -> String
$cshowList :: [RestTableReference] -> ShowS
showList :: [RestTableReference] -> ShowS
Show, (forall x. RestTableReference -> Rep RestTableReference x)
-> (forall x. Rep RestTableReference x -> RestTableReference)
-> Generic RestTableReference
forall x. Rep RestTableReference x -> RestTableReference
forall x. RestTableReference -> Rep RestTableReference x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RestTableReference -> Rep RestTableReference x
from :: forall x. RestTableReference -> Rep RestTableReference x
$cto :: forall x. Rep RestTableReference x -> RestTableReference
to :: forall x. Rep RestTableReference x -> RestTableReference
Generic)

instance FromJSON RestTableReference

data RestTable = RestTable
  { RestTable -> RestTableReference
tableReference :: RestTableReference,
    RestTable -> RestTableSchema
schema :: RestTableSchema
  }
  deriving (Int -> RestTable -> ShowS
[RestTable] -> ShowS
RestTable -> String
(Int -> RestTable -> ShowS)
-> (RestTable -> String)
-> ([RestTable] -> ShowS)
-> Show RestTable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestTable -> ShowS
showsPrec :: Int -> RestTable -> ShowS
$cshow :: RestTable -> String
show :: RestTable -> String
$cshowList :: [RestTable] -> ShowS
showList :: [RestTable] -> ShowS
Show, (forall x. RestTable -> Rep RestTable x)
-> (forall x. Rep RestTable x -> RestTable) -> Generic RestTable
forall x. Rep RestTable x -> RestTable
forall x. RestTable -> Rep RestTable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RestTable -> Rep RestTable x
from :: forall x. RestTable -> Rep RestTable x
$cto :: forall x. Rep RestTable x -> RestTable
to :: forall x. Rep RestTable x -> RestTable
Generic)

instance FromJSON RestTable

data RestTableSchema = RestTableSchema
  { RestTableSchema -> [RestFieldSchema]
fields :: [RestFieldSchema]
  }
  deriving (Int -> RestTableSchema -> ShowS
[RestTableSchema] -> ShowS
RestTableSchema -> String
(Int -> RestTableSchema -> ShowS)
-> (RestTableSchema -> String)
-> ([RestTableSchema] -> ShowS)
-> Show RestTableSchema
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestTableSchema -> ShowS
showsPrec :: Int -> RestTableSchema -> ShowS
$cshow :: RestTableSchema -> String
show :: RestTableSchema -> String
$cshowList :: [RestTableSchema] -> ShowS
showList :: [RestTableSchema] -> ShowS
Show, (forall x. RestTableSchema -> Rep RestTableSchema x)
-> (forall x. Rep RestTableSchema x -> RestTableSchema)
-> Generic RestTableSchema
forall x. Rep RestTableSchema x -> RestTableSchema
forall x. RestTableSchema -> Rep RestTableSchema x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RestTableSchema -> Rep RestTableSchema x
from :: forall x. RestTableSchema -> Rep RestTableSchema x
$cto :: forall x. Rep RestTableSchema x -> RestTableSchema
to :: forall x. Rep RestTableSchema x -> RestTableSchema
Generic)

instance FromJSON RestTableSchema

data RestFieldSchema = RestFieldSchema
  { RestFieldSchema -> Text
name :: Text,
    -- | The field data type. Possible values include STRING, BYTES,
    -- INTEGER, INT64 (same as INTEGER), FLOAT, FLOAT64 (same as
    -- FLOAT), BOOLEAN, BOOL (same as BOOLEAN), TIMESTAMP, DATE, TIME,
    -- DATETIME, GEOGRAPHY, NUMERIC, RECORD (where RECORD indicates
    -- that the field contains a nested schema) or STRUCT (same as
    -- RECORD).
    RestFieldSchema -> RestType
type' :: RestType,
    RestFieldSchema -> Mode
mode :: Mode
    -- The field mode. Possible values include NULLABLE, REQUIRED and
    -- REPEATED. The default value is NULLABLE.
  }
  deriving (Int -> RestFieldSchema -> ShowS
[RestFieldSchema] -> ShowS
RestFieldSchema -> String
(Int -> RestFieldSchema -> ShowS)
-> (RestFieldSchema -> String)
-> ([RestFieldSchema] -> ShowS)
-> Show RestFieldSchema
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestFieldSchema -> ShowS
showsPrec :: Int -> RestFieldSchema -> ShowS
$cshow :: RestFieldSchema -> String
show :: RestFieldSchema -> String
$cshowList :: [RestFieldSchema] -> ShowS
showList :: [RestFieldSchema] -> ShowS
Show, (forall x. RestFieldSchema -> Rep RestFieldSchema x)
-> (forall x. Rep RestFieldSchema x -> RestFieldSchema)
-> Generic RestFieldSchema
forall x. Rep RestFieldSchema x -> RestFieldSchema
forall x. RestFieldSchema -> Rep RestFieldSchema x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RestFieldSchema -> Rep RestFieldSchema x
from :: forall x. RestFieldSchema -> Rep RestFieldSchema x
$cto :: forall x. Rep RestFieldSchema x -> RestFieldSchema
to :: forall x. Rep RestFieldSchema x -> RestFieldSchema
Generic)

instance FromJSON RestFieldSchema where
  parseJSON :: Value -> Parser RestFieldSchema
parseJSON =
    String
-> (Object -> Parser RestFieldSchema)
-> Value
-> Parser RestFieldSchema
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject
      String
"RestFieldSchema"
      ( \Object
o -> do
          RestType
type' <- Object
o Object -> Key -> Parser RestType
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
          Text
name <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
          Mode
mode <- Object
o Object -> Key -> Parser (Maybe Mode)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"mode" Parser (Maybe Mode) -> Mode -> Parser Mode
forall a. Parser (Maybe a) -> a -> Parser a
.!= Mode
Nullable
          RestFieldSchema -> Parser RestFieldSchema
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestFieldSchema {Text
RestType
Mode
$sel:name:RestFieldSchema :: Text
$sel:type':RestFieldSchema :: RestType
$sel:mode:RestFieldSchema :: Mode
type' :: RestType
name :: Text
mode :: Mode
..}
      )

data Mode = Nullable | Required | Repeated deriving (Int -> Mode -> ShowS
[Mode] -> ShowS
Mode -> String
(Int -> Mode -> ShowS)
-> (Mode -> String) -> ([Mode] -> ShowS) -> Show Mode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Mode -> ShowS
showsPrec :: Int -> Mode -> ShowS
$cshow :: Mode -> String
show :: Mode -> String
$cshowList :: [Mode] -> ShowS
showList :: [Mode] -> ShowS
Show)

instance FromJSON Mode where
  parseJSON :: Value -> Parser Mode
parseJSON Value
j = do
    Text
s <- Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
j
    case Text
s :: Text of
      Text
"NULLABLE" -> Mode -> Parser Mode
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Mode
Nullable
      Text
"REQUIRED" -> Mode -> Parser Mode
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Mode
Required
      Text
"REPEATED" -> Mode -> Parser Mode
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Mode
Repeated
      Text
_ -> String -> Parser Mode
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"invalid mode " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
s)

data RestType
  = STRING
  | BYTES
  | INTEGER
  | FLOAT
  | BOOL
  | TIMESTAMP
  | DATE
  | TIME
  | DATETIME
  | GEOGRAPHY
  | DECIMAL
  | BIGDECIMAL
  | JSON
  | STRUCT -- (same as RECORD).
  deriving (RestType -> RestType -> Bool
(RestType -> RestType -> Bool)
-> (RestType -> RestType -> Bool) -> Eq RestType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RestType -> RestType -> Bool
== :: RestType -> RestType -> Bool
$c/= :: RestType -> RestType -> Bool
/= :: RestType -> RestType -> Bool
Eq, Int -> RestType -> ShowS
[RestType] -> ShowS
RestType -> String
(Int -> RestType -> ShowS)
-> (RestType -> String) -> ([RestType] -> ShowS) -> Show RestType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestType -> ShowS
showsPrec :: Int -> RestType -> ShowS
$cshow :: RestType -> String
show :: RestType -> String
$cshowList :: [RestType] -> ShowS
showList :: [RestType] -> ShowS
Show)

instance FromJSON RestType where
  parseJSON :: Value -> Parser RestType
parseJSON Value
j = do
    Text
s <- Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
j
    case Text
s :: Text of
      Text
"STRING" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
STRING
      Text
"BYTES" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
BYTES
      Text
"INTEGER" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
INTEGER
      Text
"INT64" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
INTEGER
      Text
"FLOAT" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
FLOAT
      Text
"FLOAT64" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
FLOAT
      Text
"BOOLEAN" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
BOOL
      Text
"BOOL" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
BOOL
      Text
"TIMESTAMP" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
TIMESTAMP
      Text
"DATE" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
DATE
      Text
"TIME" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
TIME
      Text
"DATETIME" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
DATETIME
      Text
"GEOGRAPHY" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
GEOGRAPHY
      Text
"NUMERIC" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
DECIMAL
      Text
"DECIMAL" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
DECIMAL
      Text
"BIGNUMERIC" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
BIGDECIMAL
      Text
"BIGDECIMAL" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
BIGDECIMAL
      Text
"JSON" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
JSON
      Text
"RECORD" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
STRUCT
      Text
"STRUCT" -> RestType -> Parser RestType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RestType
STRUCT
      Text
_ -> String -> Parser RestType
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"invalid type " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
s)

instance ToJSON RestType where
  toJSON :: RestType -> Value
toJSON =
    Text -> Value
String (Text -> Value) -> (RestType -> Text) -> RestType -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
      RestType
STRING -> Text
"STRING"
      RestType
BYTES -> Text
"BYTES"
      RestType
INTEGER -> Text
"INTEGER"
      RestType
FLOAT -> Text
"FLOAT"
      RestType
BOOL -> Text
"BOOLEAN"
      RestType
TIMESTAMP -> Text
"TIMESTAMP"
      RestType
DATE -> Text
"DATE"
      RestType
TIME -> Text
"TIME"
      RestType
DATETIME -> Text
"DATETIME"
      RestType
GEOGRAPHY -> Text
"GEOGRAPHY"
      RestType
DECIMAL -> Text
"DECIMAL"
      RestType
BIGDECIMAL -> Text
"BIGDECIMAL"
      RestType
JSON -> Text
"JSON"
      RestType
STRUCT -> Text
"STRUCT"

--------------------------------------------------------------------------------
-- REST request

-- | Get all tables from all specified data sets.
getTables ::
  (MonadIO m) =>
  BigQuerySourceConfig ->
  m (Either RestProblem [RestTable])
getTables :: forall (m :: * -> *).
MonadIO m =>
BigQuerySourceConfig -> m (Either RestProblem [RestTable])
getTables BigQuerySourceConfig {Int64
[BigQueryDataset]
BigQueryConnection
_scConnection :: BigQueryConnection
_scDatasets :: [BigQueryDataset]
_scGlobalSelectLimit :: Int64
_scConnection :: BigQuerySourceConfig -> BigQueryConnection
_scDatasets :: BigQuerySourceConfig -> [BigQueryDataset]
_scGlobalSelectLimit :: BigQuerySourceConfig -> Int64
..} =
  ExceptT RestProblem m [RestTable]
-> m (Either RestProblem [RestTable])
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT
    (([[RestTable]] -> [RestTable])
-> ExceptT RestProblem m [[RestTable]]
-> ExceptT RestProblem m [RestTable]
forall a b.
(a -> b) -> ExceptT RestProblem m a -> ExceptT RestProblem m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[RestTable]] -> [RestTable]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ((BigQueryDataset -> ExceptT RestProblem m [RestTable])
-> [BigQueryDataset] -> ExceptT RestProblem m [[RestTable]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (m (Either RestProblem [RestTable])
-> ExceptT RestProblem m [RestTable]
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either RestProblem [RestTable])
 -> ExceptT RestProblem m [RestTable])
-> (BigQueryDataset -> m (Either RestProblem [RestTable]))
-> BigQueryDataset
-> ExceptT RestProblem m [RestTable]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BigQueryConnection
-> BigQueryDataset -> m (Either RestProblem [RestTable])
forall (m :: * -> *).
MonadIO m =>
BigQueryConnection
-> BigQueryDataset -> m (Either RestProblem [RestTable])
getTablesForDataSet BigQueryConnection
_scConnection) [BigQueryDataset]
_scDatasets))

-- | Get tables in the dataset.
getTablesForDataSet ::
  (MonadIO m) =>
  BigQueryConnection ->
  BigQueryDataset ->
  m (Either RestProblem [RestTable])
getTablesForDataSet :: forall (m :: * -> *).
MonadIO m =>
BigQueryConnection
-> BigQueryDataset -> m (Either RestProblem [RestTable])
getTablesForDataSet BigQueryConnection
conn BigQueryDataset
dataSet = do
  Either RestProblem [RestTableBrief]
result <-
    IO (Either RestProblem [RestTableBrief])
-> m (Either RestProblem [RestTableBrief])
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either RestProblem [RestTableBrief])
-> (SomeException -> IO (Either RestProblem [RestTableBrief]))
-> IO (Either RestProblem [RestTableBrief])
forall (m :: * -> *) a.
MonadCatch m =>
m a -> (SomeException -> m a) -> m a
catchAny (Maybe Text
-> Seq RestTableBrief -> IO (Either RestProblem [RestTableBrief])
run Maybe Text
forall a. Maybe a
Nothing Seq RestTableBrief
forall a. Monoid a => a
mempty) (Either RestProblem [RestTableBrief]
-> IO (Either RestProblem [RestTableBrief])
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either RestProblem [RestTableBrief]
 -> IO (Either RestProblem [RestTableBrief]))
-> (SomeException -> Either RestProblem [RestTableBrief])
-> SomeException
-> IO (Either RestProblem [RestTableBrief])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RestProblem -> Either RestProblem [RestTableBrief]
forall a b. a -> Either a b
Left (RestProblem -> Either RestProblem [RestTableBrief])
-> (SomeException -> RestProblem)
-> SomeException
-> Either RestProblem [RestTableBrief]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> RestProblem
GetTablesProblem))
  case Either RestProblem [RestTableBrief]
result of
    Left RestProblem
e -> Either RestProblem [RestTable]
-> m (Either RestProblem [RestTable])
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RestProblem -> Either RestProblem [RestTable]
forall a b. a -> Either a b
Left RestProblem
e)
    Right [RestTableBrief]
briefs ->
      ([Either RestProblem RestTable] -> Either RestProblem [RestTable])
-> m [Either RestProblem RestTable]
-> m (Either RestProblem [RestTable])
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
        [Either RestProblem RestTable] -> Either RestProblem [RestTable]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence
        ( (RestTableBrief -> m (Either RestProblem RestTable))
-> [RestTableBrief] -> m [Either RestProblem RestTable]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse
            ( \RestTableBrief {$sel:tableReference:RestTableBrief :: RestTableBrief -> RestTableReference
tableReference = RestTableReference {Text
$sel:tableId:RestTableReference :: RestTableReference -> Text
tableId :: Text
tableId}} ->
                BigQueryConnection
-> BigQueryDataset -> Text -> m (Either RestProblem RestTable)
forall (m :: * -> *).
MonadIO m =>
BigQueryConnection
-> BigQueryDataset -> Text -> m (Either RestProblem RestTable)
getTable BigQueryConnection
conn BigQueryDataset
dataSet Text
tableId
            )
            [RestTableBrief]
briefs
        )
  where
    run :: Maybe Text
-> Seq RestTableBrief -> IO (Either RestProblem [RestTableBrief])
run Maybe Text
pageToken Seq RestTableBrief
acc = do
      let req :: Request
req =
            HeaderName -> [ByteString] -> Request -> Request
setRequestHeader HeaderName
"Content-Type" [ByteString
"application/json"]
              (Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$ String -> Request
parseRequest_ String
url
      Either BigQueryProblem (Response ByteString)
eResp <- BigQueryConnection
-> Request -> IO (Either BigQueryProblem (Response ByteString))
forall (m :: * -> *).
MonadIO m =>
BigQueryConnection
-> Request -> m (Either BigQueryProblem (Response ByteString))
runBigQuery BigQueryConnection
conn Request
req
      case Either BigQueryProblem (Response ByteString)
eResp of
        Left BigQueryProblem
e -> Either RestProblem [RestTableBrief]
-> IO (Either RestProblem [RestTableBrief])
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RestProblem -> Either RestProblem [RestTableBrief]
forall a b. a -> Either a b
Left (BigQueryProblem -> RestProblem
GetTablesBigQueryProblem BigQueryProblem
e))
        Right Response ByteString
resp ->
          case Response ByteString -> Int
forall a. Response a -> Int
getResponseStatusCode Response ByteString
resp of
            Int
200 ->
              case ByteString -> Either String RestTableList
forall a. FromJSON a => ByteString -> Either String a
J.eitherDecode (Response ByteString -> ByteString
forall a. Response a -> a
getResponseBody Response ByteString
resp) of
                Left String
e -> Either RestProblem [RestTableBrief]
-> IO (Either RestProblem [RestTableBrief])
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RestProblem -> Either RestProblem [RestTableBrief]
forall a b. a -> Either a b
Left (String -> RestProblem
GetMetaDecodeProblem String
e))
                Right RestTableList {Maybe Text
$sel:nextPageToken:RestTableList :: RestTableList -> Maybe Text
nextPageToken :: Maybe Text
nextPageToken, [RestTableBrief]
$sel:tables:RestTableList :: RestTableList -> [RestTableBrief]
tables :: [RestTableBrief]
tables} ->
                  case Maybe Text
nextPageToken of
                    Maybe Text
Nothing -> Either RestProblem [RestTableBrief]
-> IO (Either RestProblem [RestTableBrief])
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([RestTableBrief] -> Either RestProblem [RestTableBrief]
forall a b. b -> Either a b
Right (Seq RestTableBrief -> [RestTableBrief]
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (Seq RestTableBrief
acc Seq RestTableBrief -> Seq RestTableBrief -> Seq RestTableBrief
forall a. Semigroup a => a -> a -> a
<> [RestTableBrief] -> Seq RestTableBrief
forall a. [a] -> Seq a
Seq.fromList [RestTableBrief]
tables)))
                    Just Text
token -> Maybe Text
-> Seq RestTableBrief -> IO (Either RestProblem [RestTableBrief])
run (Text -> Maybe Text
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
token) (Seq RestTableBrief
acc Seq RestTableBrief -> Seq RestTableBrief -> Seq RestTableBrief
forall a. Semigroup a => a -> a -> a
<> [RestTableBrief] -> Seq RestTableBrief
forall a. [a] -> Seq a
Seq.fromList [RestTableBrief]
tables)
            Int
_ -> Either RestProblem [RestTableBrief]
-> IO (Either RestProblem [RestTableBrief])
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RestProblem -> Either RestProblem [RestTableBrief]
forall a b. a -> Either a b
Left (Status -> RestProblem
RESTRequestNonOK (Response ByteString -> Status
forall a. Response a -> Status
getResponseStatus Response ByteString
resp)))
      where
        url :: String
url =
          Text -> String
T.unpack
            (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Text
"GET https://bigquery.googleapis.com/bigquery/v2/projects/"
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> BigQueryProjectId -> Text
getBigQueryProjectId (BigQueryConnection -> BigQueryProjectId
_bqProjectId BigQueryConnection
conn)
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/datasets/"
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> BigQueryDataset -> Text
getBigQueryDataset BigQueryDataset
dataSet
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/tables?alt=json&"
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [(Text, Text)] -> Text
encodeParams [(Text, Text)]
extraParameters
        extraParameters :: [(Text, Text)]
extraParameters = [(Text, Text)]
pageTokenParam
          where
            pageTokenParam :: [(Text, Text)]
pageTokenParam =
              case Maybe Text
pageToken of
                Maybe Text
Nothing -> []
                Just Text
token -> [(Text
"pageToken", Text
token)]

-- | Get tables in the schema.
getTable ::
  (MonadIO m) =>
  BigQueryConnection ->
  BigQueryDataset ->
  Text ->
  m (Either RestProblem RestTable)
getTable :: forall (m :: * -> *).
MonadIO m =>
BigQueryConnection
-> BigQueryDataset -> Text -> m (Either RestProblem RestTable)
getTable BigQueryConnection
conn BigQueryDataset
dataSet Text
tableId = do
  IO (Either RestProblem RestTable)
-> m (Either RestProblem RestTable)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either RestProblem RestTable)
-> (SomeException -> IO (Either RestProblem RestTable))
-> IO (Either RestProblem RestTable)
forall (m :: * -> *) a.
MonadCatch m =>
m a -> (SomeException -> m a) -> m a
catchAny IO (Either RestProblem RestTable)
run (Either RestProblem RestTable -> IO (Either RestProblem RestTable)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either RestProblem RestTable -> IO (Either RestProblem RestTable))
-> (SomeException -> Either RestProblem RestTable)
-> SomeException
-> IO (Either RestProblem RestTable)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RestProblem -> Either RestProblem RestTable
forall a b. a -> Either a b
Left (RestProblem -> Either RestProblem RestTable)
-> (SomeException -> RestProblem)
-> SomeException
-> Either RestProblem RestTable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> RestProblem
GetTableProblem))
  where
    run :: IO (Either RestProblem RestTable)
run = do
      let req :: Request
req =
            HeaderName -> [ByteString] -> Request -> Request
setRequestHeader HeaderName
"Content-Type" [ByteString
"application/json"]
              (Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$ String -> Request
parseRequest_ String
url
      Either BigQueryProblem (Response ByteString)
eResp <- BigQueryConnection
-> Request -> IO (Either BigQueryProblem (Response ByteString))
forall (m :: * -> *).
MonadIO m =>
BigQueryConnection
-> Request -> m (Either BigQueryProblem (Response ByteString))
runBigQuery BigQueryConnection
conn Request
req
      case Either BigQueryProblem (Response ByteString)
eResp of
        Left BigQueryProblem
e -> Either RestProblem RestTable -> IO (Either RestProblem RestTable)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RestProblem -> Either RestProblem RestTable
forall a b. a -> Either a b
Left (BigQueryProblem -> RestProblem
GetTablesBigQueryProblem BigQueryProblem
e))
        Right Response ByteString
resp ->
          case Response ByteString -> Int
forall a. Response a -> Int
getResponseStatusCode Response ByteString
resp of
            Int
200 ->
              case ByteString -> Either String RestTable
forall a. FromJSON a => ByteString -> Either String a
J.eitherDecode (Response ByteString -> ByteString
forall a. Response a -> a
getResponseBody Response ByteString
resp) of
                Left String
e -> Either RestProblem RestTable -> IO (Either RestProblem RestTable)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RestProblem -> Either RestProblem RestTable
forall a b. a -> Either a b
Left (String -> RestProblem
GetMetaDecodeProblem String
e))
                Right RestTable
table -> Either RestProblem RestTable -> IO (Either RestProblem RestTable)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RestTable -> Either RestProblem RestTable
forall a b. b -> Either a b
Right RestTable
table)
            Int
_ -> Either RestProblem RestTable -> IO (Either RestProblem RestTable)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RestProblem -> Either RestProblem RestTable
forall a b. a -> Either a b
Left (Status -> RestProblem
RESTRequestNonOK (Response ByteString -> Status
forall a. Response a -> Status
getResponseStatus Response ByteString
resp)))
      where
        url :: String
url =
          Text -> String
T.unpack
            (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Text
"GET https://bigquery.googleapis.com/bigquery/v2/projects/"
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> BigQueryProjectId -> Text
getBigQueryProjectId (BigQueryConnection -> BigQueryProjectId
_bqProjectId BigQueryConnection
conn)
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/datasets/"
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> BigQueryDataset -> Text
getBigQueryDataset BigQueryDataset
dataSet
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/tables/"
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
tableId
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"?alt=json&"
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [(Text, Text)] -> Text
encodeParams [(Text, Text)]
forall a. [a]
extraParameters
        extraParameters :: [a]
extraParameters = []

encodeParams :: [(Text, Text)] -> Text
encodeParams :: [(Text, Text)] -> Text
encodeParams = Text -> [Text] -> Text
T.intercalate Text
"&" ([Text] -> Text)
-> ([(Text, Text)] -> [Text]) -> [(Text, Text)] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Text, Text) -> Text) -> [(Text, Text)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (\(Text
k, Text
v) -> Text
k Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
v)

-- Routines related

-- | The fine-grained type of the routine
-- Ref: https://cloud.google.com/bigquery/docs/reference/rest/v2/routines#RoutineType
data RestRoutineType
  = ROUTINE_TYPE_UNSPECIFIED
  | SCALAR_FUNCTION
  | PROCEDURE
  | TABLE_VALUED_FUNCTION
  deriving (Int -> RestRoutineType -> ShowS
[RestRoutineType] -> ShowS
RestRoutineType -> String
(Int -> RestRoutineType -> ShowS)
-> (RestRoutineType -> String)
-> ([RestRoutineType] -> ShowS)
-> Show RestRoutineType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestRoutineType -> ShowS
showsPrec :: Int -> RestRoutineType -> ShowS
$cshow :: RestRoutineType -> String
show :: RestRoutineType -> String
$cshowList :: [RestRoutineType] -> ShowS
showList :: [RestRoutineType] -> ShowS
Show, RestRoutineType -> RestRoutineType -> Bool
(RestRoutineType -> RestRoutineType -> Bool)
-> (RestRoutineType -> RestRoutineType -> Bool)
-> Eq RestRoutineType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RestRoutineType -> RestRoutineType -> Bool
== :: RestRoutineType -> RestRoutineType -> Bool
$c/= :: RestRoutineType -> RestRoutineType -> Bool
/= :: RestRoutineType -> RestRoutineType -> Bool
Eq, (forall x. RestRoutineType -> Rep RestRoutineType x)
-> (forall x. Rep RestRoutineType x -> RestRoutineType)
-> Generic RestRoutineType
forall x. Rep RestRoutineType x -> RestRoutineType
forall x. RestRoutineType -> Rep RestRoutineType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RestRoutineType -> Rep RestRoutineType x
from :: forall x. RestRoutineType -> Rep RestRoutineType x
$cto :: forall x. Rep RestRoutineType x -> RestRoutineType
to :: forall x. Rep RestRoutineType x -> RestRoutineType
Generic)

instance FromJSON RestRoutineType

instance ToJSON RestRoutineType

-- | Input argument of a function/routine.
-- Ref: https://cloud.google.com/bigquery/docs/reference/rest/v2/routines#Argument
data RestArgument = RestArgument
  { -- | The name of this argument. Can be absent for function return argument.
    RestArgument -> Maybe Text
_raName :: Maybe Text,
    RestArgument -> Maybe RestType
_raDataType :: Maybe RestType
  }
  deriving (RestArgument -> RestArgument -> Bool
(RestArgument -> RestArgument -> Bool)
-> (RestArgument -> RestArgument -> Bool) -> Eq RestArgument
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RestArgument -> RestArgument -> Bool
== :: RestArgument -> RestArgument -> Bool
$c/= :: RestArgument -> RestArgument -> Bool
/= :: RestArgument -> RestArgument -> Bool
Eq, Int -> RestArgument -> ShowS
[RestArgument] -> ShowS
RestArgument -> String
(Int -> RestArgument -> ShowS)
-> (RestArgument -> String)
-> ([RestArgument] -> ShowS)
-> Show RestArgument
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestArgument -> ShowS
showsPrec :: Int -> RestArgument -> ShowS
$cshow :: RestArgument -> String
show :: RestArgument -> String
$cshowList :: [RestArgument] -> ShowS
showList :: [RestArgument] -> ShowS
Show, (forall x. RestArgument -> Rep RestArgument x)
-> (forall x. Rep RestArgument x -> RestArgument)
-> Generic RestArgument
forall x. Rep RestArgument x -> RestArgument
forall x. RestArgument -> Rep RestArgument x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RestArgument -> Rep RestArgument x
from :: forall x. RestArgument -> Rep RestArgument x
$cto :: forall x. Rep RestArgument x -> RestArgument
to :: forall x. Rep RestArgument x -> RestArgument
Generic)

instance FromJSON RestArgument where
  parseJSON :: Value -> Parser RestArgument
parseJSON =
    String
-> (Object -> Parser RestArgument) -> Value -> Parser RestArgument
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject
      String
"RestArgument"
      ( \Object
o -> do
          Maybe Text
name <- Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"name"
          Maybe Object
typeObject <- Object
o Object -> Key -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"dataType"

          -- (Hopefully) very temporary fix: right now, we don't have an
          -- understanding of @ARRAY@ as a 'RestType', which is causing issues
          -- in production. With this change, we ignore any BigQuery argument
          -- types that we don't recognise. While not ideal, this should be
          -- safe, as we shouldn't get types from BigQuery that it can't itself
          -- understand.
          Maybe RestType
type' <- (Object -> Parser RestType)
-> Maybe Object -> Parser (Maybe RestType)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM (Object -> Key -> Parser RestType
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"typeKind") Maybe Object
typeObject Parser (Maybe RestType)
-> Parser (Maybe RestType) -> Parser (Maybe RestType)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe RestType -> Parser (Maybe RestType)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe RestType
forall a. Maybe a
Nothing
          RestArgument -> Parser RestArgument
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RestArgument -> Parser RestArgument)
-> RestArgument -> Parser RestArgument
forall a b. (a -> b) -> a -> b
$ Maybe Text -> Maybe RestType -> RestArgument
RestArgument Maybe Text
name Maybe RestType
type'
      )

instance ToJSON RestArgument where
  toJSON :: RestArgument -> Value
toJSON (RestArgument Maybe Text
name Maybe RestType
ty) =
    [Pair] -> Value
object
      [ Key
"name" Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Maybe Text
name,
        Key
"dataType" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= [Pair] -> Value
object [Key
"typeKind" Key -> Maybe RestType -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Maybe RestType
ty]
      ]

-- | A field or a column.
-- Ref: https://cloud.google.com/bigquery/docs/reference/rest/v2/StandardSqlField
data RestStandardSqlField = RestStandardSqlField
  { -- | The field name is optional and is absent for fields with STRUCT type.
    RestStandardSqlField -> Maybe Text
_rssfName :: Maybe Text,
    RestStandardSqlField -> Maybe RestType
_rssType :: Maybe RestType
  }
  deriving (RestStandardSqlField -> RestStandardSqlField -> Bool
(RestStandardSqlField -> RestStandardSqlField -> Bool)
-> (RestStandardSqlField -> RestStandardSqlField -> Bool)
-> Eq RestStandardSqlField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RestStandardSqlField -> RestStandardSqlField -> Bool
== :: RestStandardSqlField -> RestStandardSqlField -> Bool
$c/= :: RestStandardSqlField -> RestStandardSqlField -> Bool
/= :: RestStandardSqlField -> RestStandardSqlField -> Bool
Eq, Int -> RestStandardSqlField -> ShowS
[RestStandardSqlField] -> ShowS
RestStandardSqlField -> String
(Int -> RestStandardSqlField -> ShowS)
-> (RestStandardSqlField -> String)
-> ([RestStandardSqlField] -> ShowS)
-> Show RestStandardSqlField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestStandardSqlField -> ShowS
showsPrec :: Int -> RestStandardSqlField -> ShowS
$cshow :: RestStandardSqlField -> String
show :: RestStandardSqlField -> String
$cshowList :: [RestStandardSqlField] -> ShowS
showList :: [RestStandardSqlField] -> ShowS
Show, (forall x. RestStandardSqlField -> Rep RestStandardSqlField x)
-> (forall x. Rep RestStandardSqlField x -> RestStandardSqlField)
-> Generic RestStandardSqlField
forall x. Rep RestStandardSqlField x -> RestStandardSqlField
forall x. RestStandardSqlField -> Rep RestStandardSqlField x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RestStandardSqlField -> Rep RestStandardSqlField x
from :: forall x. RestStandardSqlField -> Rep RestStandardSqlField x
$cto :: forall x. Rep RestStandardSqlField x -> RestStandardSqlField
to :: forall x. Rep RestStandardSqlField x -> RestStandardSqlField
Generic)

instance FromJSON RestStandardSqlField where
  parseJSON :: Value -> Parser RestStandardSqlField
parseJSON =
    String
-> (Object -> Parser RestStandardSqlField)
-> Value
-> Parser RestStandardSqlField
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject
      String
"RestStandardSqlField"
      ( \Object
o -> do
          Maybe Text
name <- Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"name"
          Maybe Object
typeObject <- Object
o Object -> Key -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"type"

          -- (Hopefully) very temporary fix: right now, we don't have an
          -- understanding of @ARRAY@ as a 'RestType', which is causing issues
          -- in production. With this change, we ignore any BigQuery argument
          -- types that we don't recognise. While not ideal, this should be
          -- safe, as we shouldn't get types from BigQuery that it can't itself
          -- understand.
          Maybe RestType
type' <- (Object -> Parser RestType)
-> Maybe Object -> Parser (Maybe RestType)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM (Object -> Key -> Parser RestType
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"typeKind") Maybe Object
typeObject Parser (Maybe RestType)
-> Parser (Maybe RestType) -> Parser (Maybe RestType)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe RestType -> Parser (Maybe RestType)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe RestType
forall a. Maybe a
Nothing
          RestStandardSqlField -> Parser RestStandardSqlField
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RestStandardSqlField -> Parser RestStandardSqlField)
-> RestStandardSqlField -> Parser RestStandardSqlField
forall a b. (a -> b) -> a -> b
$ Maybe Text -> Maybe RestType -> RestStandardSqlField
RestStandardSqlField Maybe Text
name Maybe RestType
type'
      )

instance ToJSON RestStandardSqlField where
  toJSON :: RestStandardSqlField -> Value
toJSON (RestStandardSqlField Maybe Text
name Maybe RestType
ty) =
    [Pair] -> Value
object [Key
"name" Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Maybe Text
name, Key
"type" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ([Pair] -> Value
object [Key
"typeKind" Key -> Maybe RestType -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Maybe RestType
ty])]

-- | A table type, which has only list of columns with names and types.
-- Ref: https://cloud.google.com/bigquery/docs/reference/rest/v2/routines#StandardSqlTableType
data RestStandardSqlTableType = RestStandardSqlTableType
  { RestStandardSqlTableType -> [RestStandardSqlField]
_rrttColumns :: [RestStandardSqlField]
  }
  deriving (RestStandardSqlTableType -> RestStandardSqlTableType -> Bool
(RestStandardSqlTableType -> RestStandardSqlTableType -> Bool)
-> (RestStandardSqlTableType -> RestStandardSqlTableType -> Bool)
-> Eq RestStandardSqlTableType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RestStandardSqlTableType -> RestStandardSqlTableType -> Bool
== :: RestStandardSqlTableType -> RestStandardSqlTableType -> Bool
$c/= :: RestStandardSqlTableType -> RestStandardSqlTableType -> Bool
/= :: RestStandardSqlTableType -> RestStandardSqlTableType -> Bool
Eq, Int -> RestStandardSqlTableType -> ShowS
[RestStandardSqlTableType] -> ShowS
RestStandardSqlTableType -> String
(Int -> RestStandardSqlTableType -> ShowS)
-> (RestStandardSqlTableType -> String)
-> ([RestStandardSqlTableType] -> ShowS)
-> Show RestStandardSqlTableType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestStandardSqlTableType -> ShowS
showsPrec :: Int -> RestStandardSqlTableType -> ShowS
$cshow :: RestStandardSqlTableType -> String
show :: RestStandardSqlTableType -> String
$cshowList :: [RestStandardSqlTableType] -> ShowS
showList :: [RestStandardSqlTableType] -> ShowS
Show, (forall x.
 RestStandardSqlTableType -> Rep RestStandardSqlTableType x)
-> (forall x.
    Rep RestStandardSqlTableType x -> RestStandardSqlTableType)
-> Generic RestStandardSqlTableType
forall x.
Rep RestStandardSqlTableType x -> RestStandardSqlTableType
forall x.
RestStandardSqlTableType -> Rep RestStandardSqlTableType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
RestStandardSqlTableType -> Rep RestStandardSqlTableType x
from :: forall x.
RestStandardSqlTableType -> Rep RestStandardSqlTableType x
$cto :: forall x.
Rep RestStandardSqlTableType x -> RestStandardSqlTableType
to :: forall x.
Rep RestStandardSqlTableType x -> RestStandardSqlTableType
Generic)

instance FromJSON RestStandardSqlTableType where
  parseJSON :: Value -> Parser RestStandardSqlTableType
parseJSON = Options -> Value -> Parser RestStandardSqlTableType
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
hasuraJSON

instance ToJSON RestStandardSqlTableType where
  toJSON :: RestStandardSqlTableType -> Value
toJSON = Options -> RestStandardSqlTableType -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON

-- | Id path of a routine.
-- Ref: https://cloud.google.com/bigquery/docs/reference/rest/v2/routines#RoutineReference
data RestRoutineReference = RestRoutineReference
  { RestRoutineReference -> Text
datasetId :: Text,
    RestRoutineReference -> Text
projectId :: Text,
    RestRoutineReference -> Text
routineId :: Text
  }
  deriving (RestRoutineReference -> RestRoutineReference -> Bool
(RestRoutineReference -> RestRoutineReference -> Bool)
-> (RestRoutineReference -> RestRoutineReference -> Bool)
-> Eq RestRoutineReference
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RestRoutineReference -> RestRoutineReference -> Bool
== :: RestRoutineReference -> RestRoutineReference -> Bool
$c/= :: RestRoutineReference -> RestRoutineReference -> Bool
/= :: RestRoutineReference -> RestRoutineReference -> Bool
Eq, Int -> RestRoutineReference -> ShowS
[RestRoutineReference] -> ShowS
RestRoutineReference -> String
(Int -> RestRoutineReference -> ShowS)
-> (RestRoutineReference -> String)
-> ([RestRoutineReference] -> ShowS)
-> Show RestRoutineReference
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestRoutineReference -> ShowS
showsPrec :: Int -> RestRoutineReference -> ShowS
$cshow :: RestRoutineReference -> String
show :: RestRoutineReference -> String
$cshowList :: [RestRoutineReference] -> ShowS
showList :: [RestRoutineReference] -> ShowS
Show, (forall x. RestRoutineReference -> Rep RestRoutineReference x)
-> (forall x. Rep RestRoutineReference x -> RestRoutineReference)
-> Generic RestRoutineReference
forall x. Rep RestRoutineReference x -> RestRoutineReference
forall x. RestRoutineReference -> Rep RestRoutineReference x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RestRoutineReference -> Rep RestRoutineReference x
from :: forall x. RestRoutineReference -> Rep RestRoutineReference x
$cto :: forall x. Rep RestRoutineReference x -> RestRoutineReference
to :: forall x. Rep RestRoutineReference x -> RestRoutineReference
Generic)

instance FromJSON RestRoutineReference

instance ToJSON RestRoutineReference

routineReferenceToFunctionName :: RestRoutineReference -> FunctionName
routineReferenceToFunctionName :: RestRoutineReference -> FunctionName
routineReferenceToFunctionName RestRoutineReference {Text
$sel:datasetId:RestRoutineReference :: RestRoutineReference -> Text
$sel:projectId:RestRoutineReference :: RestRoutineReference -> Text
$sel:routineId:RestRoutineReference :: RestRoutineReference -> Text
datasetId :: Text
projectId :: Text
routineId :: Text
..} =
  FunctionName {$sel:functionName:FunctionName :: Text
functionName = Text
routineId, $sel:functionNameSchema:FunctionName :: Maybe Text
functionNameSchema = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
datasetId}

-- | A user-defined function.
-- Ref: https://cloud.google.com/bigquery/docs/reference/rest/v2/routines#Routine
data RestRoutine = RestRoutine
  { -- | Reference describing the ID of this routine
    RestRoutine -> RestRoutineReference
routineReference :: RestRoutineReference,
    -- | The type of routine
    RestRoutine -> RestRoutineType
routineType :: RestRoutineType,
    -- | List of arguments defined
    RestRoutine -> Maybe [RestArgument]
arguments :: Maybe [RestArgument],
    -- | Routines defined with 'RETURNS TABLE' clause has this information
    RestRoutine -> Maybe RestStandardSqlTableType
returnTableType :: Maybe RestStandardSqlTableType
  }
  deriving (RestRoutine -> RestRoutine -> Bool
(RestRoutine -> RestRoutine -> Bool)
-> (RestRoutine -> RestRoutine -> Bool) -> Eq RestRoutine
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RestRoutine -> RestRoutine -> Bool
== :: RestRoutine -> RestRoutine -> Bool
$c/= :: RestRoutine -> RestRoutine -> Bool
/= :: RestRoutine -> RestRoutine -> Bool
Eq, Int -> RestRoutine -> ShowS
[RestRoutine] -> ShowS
RestRoutine -> String
(Int -> RestRoutine -> ShowS)
-> (RestRoutine -> String)
-> ([RestRoutine] -> ShowS)
-> Show RestRoutine
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestRoutine -> ShowS
showsPrec :: Int -> RestRoutine -> ShowS
$cshow :: RestRoutine -> String
show :: RestRoutine -> String
$cshowList :: [RestRoutine] -> ShowS
showList :: [RestRoutine] -> ShowS
Show, (forall x. RestRoutine -> Rep RestRoutine x)
-> (forall x. Rep RestRoutine x -> RestRoutine)
-> Generic RestRoutine
forall x. Rep RestRoutine x -> RestRoutine
forall x. RestRoutine -> Rep RestRoutine x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RestRoutine -> Rep RestRoutine x
from :: forall x. RestRoutine -> Rep RestRoutine x
$cto :: forall x. Rep RestRoutine x -> RestRoutine
to :: forall x. Rep RestRoutine x -> RestRoutine
Generic)

instance FromJSON RestRoutine

instance ToJSON RestRoutine

-- | List of routines
-- Ref: https://cloud.google.com/bigquery/docs/reference/rest/v2/routines/list
data RestRoutineList = RestRoutineList
  { RestRoutineList -> [RestRoutine]
_rrlRoutines :: [RestRoutine],
    RestRoutineList -> Maybe Text
_rrlNextPageToken :: Maybe Text
  }
  deriving (Int -> RestRoutineList -> ShowS
[RestRoutineList] -> ShowS
RestRoutineList -> String
(Int -> RestRoutineList -> ShowS)
-> (RestRoutineList -> String)
-> ([RestRoutineList] -> ShowS)
-> Show RestRoutineList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestRoutineList -> ShowS
showsPrec :: Int -> RestRoutineList -> ShowS
$cshow :: RestRoutineList -> String
show :: RestRoutineList -> String
$cshowList :: [RestRoutineList] -> ShowS
showList :: [RestRoutineList] -> ShowS
Show)

instance FromJSON RestRoutineList where
  parseJSON :: Value -> Parser RestRoutineList
parseJSON = String
-> (Object -> Parser RestRoutineList)
-> Value
-> Parser RestRoutineList
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Object" ((Object -> Parser RestRoutineList)
 -> Value -> Parser RestRoutineList)
-> (Object -> Parser RestRoutineList)
-> Value
-> Parser RestRoutineList
forall a b. (a -> b) -> a -> b
$ \Object
o ->
    [RestRoutine] -> Maybe Text -> RestRoutineList
RestRoutineList
      ([RestRoutine] -> Maybe Text -> RestRoutineList)
-> Parser [RestRoutine] -> Parser (Maybe Text -> RestRoutineList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o
      Object -> Key -> Parser (Maybe [RestRoutine])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"routines"
      Parser (Maybe [RestRoutine])
-> [RestRoutine] -> Parser [RestRoutine]
forall a. Parser (Maybe a) -> a -> Parser a
.!= [] -- "routine" field is absent when there are no routines defined
      Parser (Maybe Text -> RestRoutineList)
-> Parser (Maybe Text) -> Parser RestRoutineList
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
      Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"nextPageToken"

-- | Get all routines from all specified data sets.
getRoutines ::
  (MonadIO m) =>
  BigQuerySourceConfig ->
  m (Either RestProblem [RestRoutine])
getRoutines :: forall (m :: * -> *).
MonadIO m =>
BigQuerySourceConfig -> m (Either RestProblem [RestRoutine])
getRoutines BigQuerySourceConfig {Int64
[BigQueryDataset]
BigQueryConnection
_scConnection :: BigQuerySourceConfig -> BigQueryConnection
_scDatasets :: BigQuerySourceConfig -> [BigQueryDataset]
_scGlobalSelectLimit :: BigQuerySourceConfig -> Int64
_scConnection :: BigQueryConnection
_scDatasets :: [BigQueryDataset]
_scGlobalSelectLimit :: Int64
..} =
  ExceptT RestProblem m [RestRoutine]
-> m (Either RestProblem [RestRoutine])
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT
    (([[RestRoutine]] -> [RestRoutine])
-> ExceptT RestProblem m [[RestRoutine]]
-> ExceptT RestProblem m [RestRoutine]
forall a b.
(a -> b) -> ExceptT RestProblem m a -> ExceptT RestProblem m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[RestRoutine]] -> [RestRoutine]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ((BigQueryDataset -> ExceptT RestProblem m [RestRoutine])
-> [BigQueryDataset] -> ExceptT RestProblem m [[RestRoutine]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (m (Either RestProblem [RestRoutine])
-> ExceptT RestProblem m [RestRoutine]
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either RestProblem [RestRoutine])
 -> ExceptT RestProblem m [RestRoutine])
-> (BigQueryDataset -> m (Either RestProblem [RestRoutine]))
-> BigQueryDataset
-> ExceptT RestProblem m [RestRoutine]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BigQueryConnection
-> BigQueryDataset -> m (Either RestProblem [RestRoutine])
forall (m :: * -> *).
MonadIO m =>
BigQueryConnection
-> BigQueryDataset -> m (Either RestProblem [RestRoutine])
getRoutinesForDataSet BigQueryConnection
_scConnection) [BigQueryDataset]
_scDatasets))

-- | Get routines in the dataset.
getRoutinesForDataSet ::
  (MonadIO m) =>
  BigQueryConnection ->
  BigQueryDataset ->
  m (Either RestProblem [RestRoutine])
getRoutinesForDataSet :: forall (m :: * -> *).
MonadIO m =>
BigQueryConnection
-> BigQueryDataset -> m (Either RestProblem [RestRoutine])
getRoutinesForDataSet BigQueryConnection
conn BigQueryDataset
dataSet = do
  IO (Either RestProblem [RestRoutine])
-> m (Either RestProblem [RestRoutine])
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either RestProblem [RestRoutine])
-> (SomeException -> IO (Either RestProblem [RestRoutine]))
-> IO (Either RestProblem [RestRoutine])
forall (m :: * -> *) a.
MonadCatch m =>
m a -> (SomeException -> m a) -> m a
catchAny (Maybe Text
-> Seq RestRoutine -> IO (Either RestProblem [RestRoutine])
run Maybe Text
forall a. Maybe a
Nothing Seq RestRoutine
forall a. Monoid a => a
mempty) (Either RestProblem [RestRoutine]
-> IO (Either RestProblem [RestRoutine])
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either RestProblem [RestRoutine]
 -> IO (Either RestProblem [RestRoutine]))
-> (SomeException -> Either RestProblem [RestRoutine])
-> SomeException
-> IO (Either RestProblem [RestRoutine])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RestProblem -> Either RestProblem [RestRoutine]
forall a b. a -> Either a b
Left (RestProblem -> Either RestProblem [RestRoutine])
-> (SomeException -> RestProblem)
-> SomeException
-> Either RestProblem [RestRoutine]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> RestProblem
GetRoutineProblem))
  where
    run :: Maybe Text
-> Seq RestRoutine -> IO (Either RestProblem [RestRoutine])
run Maybe Text
pageToken Seq RestRoutine
acc = do
      let req :: Request
req =
            HeaderName -> [ByteString] -> Request -> Request
setRequestHeader HeaderName
"Content-Type" [ByteString
"application/json"]
              (Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$ String -> Request
parseRequest_ String
url
      Either BigQueryProblem (Response ByteString)
eResp <- BigQueryConnection
-> Request -> IO (Either BigQueryProblem (Response ByteString))
forall (m :: * -> *).
MonadIO m =>
BigQueryConnection
-> Request -> m (Either BigQueryProblem (Response ByteString))
runBigQuery BigQueryConnection
conn Request
req
      case Either BigQueryProblem (Response ByteString)
eResp of
        Left BigQueryProblem
e -> Either RestProblem [RestRoutine]
-> IO (Either RestProblem [RestRoutine])
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RestProblem -> Either RestProblem [RestRoutine]
forall a b. a -> Either a b
Left (BigQueryProblem -> RestProblem
GetRoutinesBigQueryProblem BigQueryProblem
e))
        Right Response ByteString
resp ->
          case Response ByteString -> Int
forall a. Response a -> Int
getResponseStatusCode Response ByteString
resp of
            Int
200 ->
              case ByteString -> Either String RestRoutineList
forall a. FromJSON a => ByteString -> Either String a
J.eitherDecode (Response ByteString -> ByteString
forall a. Response a -> a
getResponseBody Response ByteString
resp) of
                Left String
e -> Either RestProblem [RestRoutine]
-> IO (Either RestProblem [RestRoutine])
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RestProblem -> Either RestProblem [RestRoutine]
forall a b. a -> Either a b
Left (String -> RestProblem
GetMetaDecodeProblem String
e))
                Right RestRoutineList {$sel:_rrlRoutines:RestRoutineList :: RestRoutineList -> [RestRoutine]
_rrlRoutines = [RestRoutine]
routines, $sel:_rrlNextPageToken:RestRoutineList :: RestRoutineList -> Maybe Text
_rrlNextPageToken = Maybe Text
nextPageToken} ->
                  case Maybe Text
nextPageToken of
                    Maybe Text
Nothing -> Either RestProblem [RestRoutine]
-> IO (Either RestProblem [RestRoutine])
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([RestRoutine] -> Either RestProblem [RestRoutine]
forall a b. b -> Either a b
Right (Seq RestRoutine -> [RestRoutine]
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (Seq RestRoutine
acc Seq RestRoutine -> Seq RestRoutine -> Seq RestRoutine
forall a. Semigroup a => a -> a -> a
<> [RestRoutine] -> Seq RestRoutine
forall a. [a] -> Seq a
Seq.fromList [RestRoutine]
routines)))
                    Just Text
token -> Maybe Text
-> Seq RestRoutine -> IO (Either RestProblem [RestRoutine])
run (Text -> Maybe Text
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
token) (Seq RestRoutine
acc Seq RestRoutine -> Seq RestRoutine -> Seq RestRoutine
forall a. Semigroup a => a -> a -> a
<> [RestRoutine] -> Seq RestRoutine
forall a. [a] -> Seq a
Seq.fromList [RestRoutine]
routines)
            Int
_ -> Either RestProblem [RestRoutine]
-> IO (Either RestProblem [RestRoutine])
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RestProblem -> Either RestProblem [RestRoutine]
forall a b. a -> Either a b
Left (Status -> RestProblem
RESTRequestNonOK (Response ByteString -> Status
forall a. Response a -> Status
getResponseStatus Response ByteString
resp)))
      where
        url :: String
url =
          Text -> String
T.unpack
            (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Text
"GET https://bigquery.googleapis.com/bigquery/v2/projects/"
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> BigQueryProjectId -> Text
getBigQueryProjectId (BigQueryConnection -> BigQueryProjectId
_bqProjectId BigQueryConnection
conn)
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/datasets/"
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> BigQueryDataset -> Text
getBigQueryDataset BigQueryDataset
dataSet
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/routines?alt=json&"
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [(Text, Text)] -> Text
encodeParams [(Text, Text)]
extraParameters
        extraParameters :: [(Text, Text)]
extraParameters = [(Text, Text)]
pageTokenParam [(Text, Text)] -> [(Text, Text)] -> [(Text, Text)]
forall a. Semigroup a => a -> a -> a
<> [(Text, Text)]
readMaskParam
          where
            pageTokenParam :: [(Text, Text)]
pageTokenParam =
              case Maybe Text
pageToken of
                Maybe Text
Nothing -> []
                Just Text
token -> [(Text
"pageToken", Text
token)]
            readMaskParam :: [(Text, Text)]
readMaskParam = [(Text
"readMask", Text
"routineType,arguments,returnTableType")]