| Safe Haskell | None |
|---|---|
| Language | GHC2024 |
Napkin.Run.BigQuery
Contents
Synopsis
- normalizeTableNames :: BQProjectId -> Set (Ref Table) -> Map (Ref Table) NormalizedTable
- bqGetAnnotations :: MonadNapkin BigQuery m => BQProjectId -> Ref Table -> GoogleEnv -> m TableAnnotations
- renderBigQuery :: TableWriteStrategy -> Text
- pattern MaxResults :: Word32
- exec :: forall a (scopes :: [Symbol]) m. (GoogleRequest a, KnownScopes scopes, SatisfyScope (Scopes a) scopes, MonadIO m) => Env scopes -> a -> m (Rs a)
- exec404 :: forall a (scopes :: [Symbol]) m e. (GoogleRequest a, KnownScopes scopes, SatisfyScope (Scopes a) scopes, MonadIO m) => e -> e -> Env scopes -> a -> m e
- getTableInfo :: MonadNapkin BigQuery m => GoogleEnv -> BQProjectId -> Ref Table -> m Table
- listTables :: MonadNapkin BigQuery m => GoogleEnv -> BQProjectId -> Prefix -> m (Set ListedTable)
- extractNormalized' :: BQProjectId -> Ref Table -> Either Text NormalizedTable
- extractNormalized :: BQProjectId -> Ref Table -> Either Text NormalizedTable
- bqValidator :: (SpecDependency -> Ref Table) -> SpecsDepsTables -> [WithSpecTable Text]
- newtype Dollars = Dollars {
- _unDollars :: Fixed E2
- calcBytesCost :: Int64 -> Dollars
- data JobInfo = JobInfo {
- jobId :: !Text
- startedAt :: !UTCTime
- finishedAt :: !UTCTime
- rowsAffected :: !(Maybe Int64)
- bytesAffected :: !(Maybe Int64)
- slotTime :: !(Maybe NominalDiffTime)
- calcCost :: MonadNapkin BigQuery m => (UTCTime, Job, UTCTime) -> m Job
- executeQuery :: (MonadNapkin BigQuery m, RenderSql q BigQuery) => BQProjectId -> Labels -> q -> GoogleEnv -> m Job
- bqRunQuery :: (MonadNapkin BigQuery m, RenderSql q BigQuery) => BQProjectId -> Labels -> q -> GoogleEnv -> m [Map Text Value]
- jobQueryStats :: (UTCTime, Job, UTCTime) -> QueryStats BigQuery
- bqCopyTable :: MonadNapkin BigQuery m => BQProjectId -> Labels -> Ref Table -> Ref Table -> TableWriteStrategy -> GoogleEnv -> m ()
- bqObtainTableKind :: MonadNapkin BigQuery m => BQProjectId -> Ref Table -> GoogleEnv -> m TableKind
- bqAnnotateTable :: MonadNapkin BigQuery m => BQProjectId -> Ref Table -> Annotation -> GoogleEnv -> m ()
- runInsertJob :: (MonadNapkin BigQuery m, RenderSql a BigQuery) => JobInsertTableName -> BQProjectId -> Labels -> a -> TableMeta -> Ref Table -> GoogleEnv -> m Job
- bqCreateTableAs :: MonadNapkin BigQuery m => BQProjectId -> Labels -> Ref Table -> Query -> TableMeta -> GoogleEnv -> m ()
- authorizeView :: MonadNapkin BigQuery m => DataSetLocks -> BQProjectId -> Ref Table -> Set BQDataSetReference -> GoogleEnv -> m ()
- createTableDDL :: MonadNapkin BigQuery m => BQProjectId -> Labels -> CreateTableSchema BigQuery -> GoogleEnv -> m ()
- jobConfigurationQuery :: Text -> JobConfigurationQuery
- jobConfiguration :: GoogleEnv -> Labels -> JobConfiguration
- jobInsert :: BQProjectId -> JobConfiguration -> BigQueryJobsInsert
- bqGetRelationSchema :: MonadNapkin BigQuery m => BQProjectId -> Ref Table -> Relation -> GoogleEnv -> m [BackendSchemaField BigQuery]
- insertAndPollJob :: MonadNapkin BigQuery m => RetryPolicy -> BigQueryJobsInsert -> GoogleEnv -> NominalDiffTime -> BQProjectId -> m (Either (NonEmpty ErrorProto) Job)
- pollJob :: GoogleEnv -> NominalDiffTime -> BQProjectId -> JobReference -> IO (Either (NonEmpty ErrorProto) Job)
- bqDropTableOrView :: MonadNapkin BigQuery m => BQProjectId -> Ref Table -> GoogleEnv -> m ()
- bqCheckTableExists :: MonadNapkin BigQuery m => BQProjectId -> Ref Table -> GoogleEnv -> m Bool
- streamJobResultsPages :: forall (m :: Type -> Type) i. MonadResource m => GoogleEnv -> Job -> BQProjectId -> ConduitM i GetQueryResultsResponse m ()
- streamReq :: forall req (m :: Type -> Type) i. (AllowRequest req BigQueryScopes, MonadResource m) => GoogleEnv -> req -> Setter' req (Maybe Text) -> Getter (Rs req) (Maybe Text) -> ConduitM i (Rs req) m ()
- ndtMicros :: NominalDiffTime -> Int
- defDelay :: NominalDiffTime
- executePoll :: MonadNapkin BigQuery m => GoogleEnv -> BigQueryJobsInsert -> BQProjectId -> m (UTCTime, Job, UTCTime)
- tableInfo :: MonadNapkin BigQuery m => BQProjectId -> Ref Table -> m BigQueryTablesGet
- mkBigQueryEnvWithJsonCredentials :: (MonadCatch m, MonadNapkin BigQuery m) => Maybe Text -> CredentialsJson -> DbBackendOptions BigQuery -> BQProjectId -> m (BackendConn BigQuery)
- mkBigQueryEnvWithCredentials :: (MonadCatch m, MonadNapkin BigQuery m) => Maybe Text -> Credentials BigQueryScopes -> DbBackendOptions BigQuery -> BQProjectId -> m (BackendConn BigQuery)
- mkBigQueryEnv' :: (MonadCatch m, MonadIO m) => Natural -> IO GoogleEnv -> BQProjectId -> Labels -> m (BackendConn BigQuery)
- data BigQueryURI = BigQueryURI {}
- newtype DataSetLock = DataSetLock (MVar ())
- type DataSetLocks = TVar (Map BQDataSetId DataSetLock)
- getDataSetLock :: MonadIO m => DataSetLocks -> BQDataSetId -> m DataSetLock
- withDataSetLock :: MonadUnliftIO m => DataSetLock -> m a -> m a
- withDataSetLock' :: MonadUnliftIO m => DataSetLocks -> BQDataSetId -> m a -> m a
- parseBigQueryURI :: Text -> Maybe BigQueryURI
Documentation
normalizeTableNames :: BQProjectId -> Set (Ref Table) -> Map (Ref Table) NormalizedTable #
bqGetAnnotations :: MonadNapkin BigQuery m => BQProjectId -> Ref Table -> GoogleEnv -> m TableAnnotations #
pattern MaxResults :: Word32 #
exec :: forall a (scopes :: [Symbol]) m. (GoogleRequest a, KnownScopes scopes, SatisfyScope (Scopes a) scopes, MonadIO m) => Env scopes -> a -> m (Rs a) #
exec404 :: forall a (scopes :: [Symbol]) m e. (GoogleRequest a, KnownScopes scopes, SatisfyScope (Scopes a) scopes, MonadIO m) => e -> e -> Env scopes -> a -> m e #
getTableInfo :: MonadNapkin BigQuery m => GoogleEnv -> BQProjectId -> Ref Table -> m Table #
listTables :: MonadNapkin BigQuery m => GoogleEnv -> BQProjectId -> Prefix -> m (Set ListedTable) #
extractNormalized' :: BQProjectId -> Ref Table -> Either Text NormalizedTable #
BigQuery Names generally speaking have only three sections, subdivided by ".". Names cannot include a "." internally. But INFORMATION_SCHEMA views (read-only, system-defined views that provide metadata information about BigQuery objects) will have a "." in the name to demarcate. So there is an individual view called INFORMATION_SCHEMA.TABLES, one called INFORMATION_SCHEMA.VIEWS etc. If we wish to run against INFORMATION_SCHEMA views, we need to be a little clever in parsing them, allowing for the possibility that in fact two individual name segments actually are part of one view name.
extractNormalized :: BQProjectId -> Ref Table -> Either Text NormalizedTable #
bqValidator :: (SpecDependency -> Ref Table) -> SpecsDepsTables -> [WithSpecTable Text] #
Constructors
| Dollars | |
Fields
| |
Instances
| ToJSON Dollars # | |||||
| Generic Dollars # | |||||
Defined in Napkin.Run.BigQuery Associated Types
| |||||
| Num Dollars # | |||||
| Real Dollars # | |||||
Defined in Napkin.Run.BigQuery Methods toRational :: Dollars -> Rational # | |||||
| Show Dollars # | |||||
| Eq Dollars # | |||||
| Ord Dollars # | |||||
| type Rep Dollars # | |||||
Defined in Napkin.Run.BigQuery | |||||
calcBytesCost :: Int64 -> Dollars #
Constructors
| JobInfo | |
Fields
| |
Instances
executeQuery :: (MonadNapkin BigQuery m, RenderSql q BigQuery) => BQProjectId -> Labels -> q -> GoogleEnv -> m Job #
bqRunQuery :: (MonadNapkin BigQuery m, RenderSql q BigQuery) => BQProjectId -> Labels -> q -> GoogleEnv -> m [Map Text Value] #
jobQueryStats :: (UTCTime, Job, UTCTime) -> QueryStats BigQuery #
bqCopyTable :: MonadNapkin BigQuery m => BQProjectId -> Labels -> Ref Table -> Ref Table -> TableWriteStrategy -> GoogleEnv -> m () #
bqObtainTableKind :: MonadNapkin BigQuery m => BQProjectId -> Ref Table -> GoogleEnv -> m TableKind #
bqAnnotateTable :: MonadNapkin BigQuery m => BQProjectId -> Ref Table -> Annotation -> GoogleEnv -> m () #
runInsertJob :: (MonadNapkin BigQuery m, RenderSql a BigQuery) => JobInsertTableName -> BQProjectId -> Labels -> a -> TableMeta -> Ref Table -> GoogleEnv -> m Job #
bqCreateTableAs :: MonadNapkin BigQuery m => BQProjectId -> Labels -> Ref Table -> Query -> TableMeta -> GoogleEnv -> m () #
authorizeView :: MonadNapkin BigQuery m => DataSetLocks -> BQProjectId -> Ref Table -> Set BQDataSetReference -> GoogleEnv -> m () #
createTableDDL :: MonadNapkin BigQuery m => BQProjectId -> Labels -> CreateTableSchema BigQuery -> GoogleEnv -> m () #
jobConfiguration :: GoogleEnv -> Labels -> JobConfiguration #
bqGetRelationSchema :: MonadNapkin BigQuery m => BQProjectId -> Ref Table -> Relation -> GoogleEnv -> m [BackendSchemaField BigQuery] #
insertAndPollJob :: MonadNapkin BigQuery m => RetryPolicy -> BigQueryJobsInsert -> GoogleEnv -> NominalDiffTime -> BQProjectId -> m (Either (NonEmpty ErrorProto) Job) #
Combines inserting a job and waiting for it to finish. If the job returns *only* server errors, which require retry, it will reenqueue and retry them as per the policy.
pollJob :: GoogleEnv -> NominalDiffTime -> BQProjectId -> JobReference -> IO (Either (NonEmpty ErrorProto) Job) #
Polls a job until it finishes
bqDropTableOrView :: MonadNapkin BigQuery m => BQProjectId -> Ref Table -> GoogleEnv -> m () #
bqCheckTableExists :: MonadNapkin BigQuery m => BQProjectId -> Ref Table -> GoogleEnv -> m Bool #
streamJobResultsPages :: forall (m :: Type -> Type) i. MonadResource m => GoogleEnv -> Job -> BQProjectId -> ConduitM i GetQueryResultsResponse m () #
Arguments
| :: forall req (m :: Type -> Type) i. (AllowRequest req BigQueryScopes, MonadResource m) | |
| => GoogleEnv | |
| -> req | |
| -> Setter' req (Maybe Text) | Request's page token |
| -> Getter (Rs req) (Maybe Text) | Response's page token |
| -> ConduitM i (Rs req) m () |
This probably belongs in gogol. Given an initial request and a way to get the response's next page token and set the requests next page token, repeatedly issue requests until pages run out.
ndtMicros :: NominalDiffTime -> Int #
executePoll :: MonadNapkin BigQuery m => GoogleEnv -> BigQueryJobsInsert -> BQProjectId -> m (UTCTime, Job, UTCTime) #
tableInfo :: MonadNapkin BigQuery m => BQProjectId -> Ref Table -> m BigQueryTablesGet #
mkBigQueryEnvWithJsonCredentials :: (MonadCatch m, MonadNapkin BigQuery m) => Maybe Text -> CredentialsJson -> DbBackendOptions BigQuery -> BQProjectId -> m (BackendConn BigQuery) #
mkBigQueryEnvWithCredentials :: (MonadCatch m, MonadNapkin BigQuery m) => Maybe Text -> Credentials BigQueryScopes -> DbBackendOptions BigQuery -> BQProjectId -> m (BackendConn BigQuery) #
mkBigQueryEnv' :: (MonadCatch m, MonadIO m) => Natural -> IO GoogleEnv -> BQProjectId -> Labels -> m (BackendConn BigQuery) #
Makes a BigQuery env, but with control over configuring how the Google environment is set up.
data BigQueryURI #
Constructors
| BigQueryURI | |
Fields
| |
newtype DataSetLock #
Constructors
| DataSetLock (MVar ()) |
type DataSetLocks = TVar (Map BQDataSetId DataSetLock) #
getDataSetLock :: MonadIO m => DataSetLocks -> BQDataSetId -> m DataSetLock #
withDataSetLock :: MonadUnliftIO m => DataSetLock -> m a -> m a #
withDataSetLock' :: MonadUnliftIO m => DataSetLocks -> BQDataSetId -> m a -> m a #
parseBigQueryURI :: Text -> Maybe BigQueryURI #
Orphan instances
| Backend BigQuery # | |||||
Associated Types
Methods injectRunInfo :: RunId -> TaskId -> BackendConn BigQuery -> BackendConn BigQuery # backendConnectionString :: BackendConn BigQuery -> ConnectionString # backendExecute :: (MonadNapkin BigQuery m, RenderSql command BigQuery) => BackendConn BigQuery -> command -> m () # backendQuery :: (MonadNapkin BigQuery m, RenderSql q BigQuery) => BackendConn BigQuery -> q -> m [Map Text Value] # backendCheckTableExists :: MonadNapkin BigQuery m => BackendConn BigQuery -> Ref Table -> m Bool # backendGetTableKind :: MonadNapkin BigQuery m => BackendConn BigQuery -> Ref Table -> m TableKind # backendGetRelationSchema :: MonadNapkin BigQuery m => BackendConn BigQuery -> Ref Table -> Relation -> m [BackendSchemaField BigQuery] # backendGetAnnotations :: MonadNapkin BigQuery m => BackendConn BigQuery -> Ref Table -> m TableAnnotations # backendAnnotate :: MonadNapkin BigQuery m => BackendConn BigQuery -> Ref Table -> Annotation -> m () # backendCreateAs :: (MonadNapkin BigQuery m, RenderSql command BigQuery, command ~ CreateRelation BigQuery) => BackendConn BigQuery -> command -> m () # backendCreate :: (MonadNapkin BigQuery m, RenderSql command BigQuery, command ~ CreateTableSchema BigQuery) => BackendConn BigQuery -> command -> m () # backendCopyTable :: (Default (BackendMeta 'KindTable BigQuery), MonadNapkin BigQuery m, RenderSql (CreateRelation BigQuery) BigQuery, RenderSql DeleteRows BigQuery, RenderSql InsertInto BigQuery) => BackendConn BigQuery -> Ref Table -> Ref Table -> TableWriteStrategy -> m () # backendDrop :: MonadNapkin BigQuery m => BackendConn BigQuery -> DropRelation -> m () # backendInsertInto :: (MonadNapkin BigQuery m, RenderSql command BigQuery, command ~ InsertInto) => BackendConn BigQuery -> command -> m () # backendRename :: MonadNapkin BigQuery m => BackendConn BigQuery -> RenameRelation -> m () # backendListTables :: MonadNapkin BigQuery m => BackendConn BigQuery -> ListTables -> m (Set ListedTable) # backendNormalize :: MonadNapkin BigQuery m => BackendConn BigQuery -> NormalizeTableNames -> m (Map (Ref Table) NormalizedTable) # backendAddColumn :: (MonadNapkin BigQuery m, RenderSql command BigQuery, command ~ AddColumnToTable) => BackendConn BigQuery -> command -> m () # backendDropColumn :: (MonadNapkin BigQuery m, RenderSql command BigQuery, command ~ DropColumnFromTable) => BackendConn BigQuery -> command -> m () # | |||||
| RunBackendConn BigQuery # | |||||
Methods runBackendConn :: LogEnv -> DbBackendOptions BigQuery -> ConnectionString -> Maybe CredentialsPath -> Maybe AuthPort -> (BackendConn BigQuery -> IO a) -> IO a # | |||||
| HasBackendSchemaField BigQuery # | |||||
Associated Types
Methods fieldName :: BackendSchemaField BigQuery -> Text # fieldType :: BackendSchemaField BigQuery -> Type # | |||||
| HasBackendQueryStats BigQuery # | |||||
Associated Types
Methods | |||||
| Generic (BackendConn BigQuery) # | |||||
Associated Types
Methods from :: BackendConn BigQuery -> Rep (BackendConn BigQuery) x # to :: Rep (BackendConn BigQuery) x -> BackendConn BigQuery # | |||||
| ToJSON (BackendQueryStats BigQuery) # | |||||
Methods toJSON :: BackendQueryStats BigQuery -> Value # toEncoding :: BackendQueryStats BigQuery -> Encoding # toJSONList :: [BackendQueryStats BigQuery] -> Value # toEncodingList :: [BackendQueryStats BigQuery] -> Encoding # omitField :: BackendQueryStats BigQuery -> Bool # | |||||
| Monoid (BackendQueryStats BigQuery) # | |||||
| Semigroup (BackendQueryStats BigQuery) # | |||||
Methods (<>) :: BackendQueryStats BigQuery -> BackendQueryStats BigQuery -> BackendQueryStats BigQuery # sconcat :: NonEmpty (BackendQueryStats BigQuery) -> BackendQueryStats BigQuery # stimes :: Integral b => b -> BackendQueryStats BigQuery -> BackendQueryStats BigQuery # | |||||
| Show (BackendSchemaField BigQuery) # | |||||
| Show (BackendQueryStats BigQuery) # | |||||
| Eq (BackendSchemaField BigQuery) # | |||||
Methods (==) :: BackendSchemaField BigQuery -> BackendSchemaField BigQuery -> Bool # (/=) :: BackendSchemaField BigQuery -> BackendSchemaField BigQuery -> Bool # | |||||
| Eq (BackendQueryStats BigQuery) # | |||||
Methods (==) :: BackendQueryStats BigQuery -> BackendQueryStats BigQuery -> Bool # (/=) :: BackendQueryStats BigQuery -> BackendQueryStats BigQuery -> Bool # | |||||