napkin-0.5.13
Copyright(c) Soostone Inc 2020
LicenseAllRightsReserved
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Napkin.Types.BigQuery

Description

 
Synopsis

Documentation

data BigQuery #

Constructors

BigQuery 

Instances

Instances details
Eq BigQuery # 
Instance details

Defined in Napkin.Types.BigQuery

Data BigQuery # 
Instance details

Defined in Napkin.Types.BigQuery

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BigQuery -> c BigQuery #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BigQuery #

toConstr :: BigQuery -> Constr #

dataTypeOf :: BigQuery -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BigQuery) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BigQuery) #

gmapT :: (forall b. Data b => b -> b) -> BigQuery -> BigQuery #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BigQuery -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BigQuery -> r #

gmapQ :: (forall d. Data d => d -> u) -> BigQuery -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BigQuery -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BigQuery -> m BigQuery #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BigQuery -> m BigQuery #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BigQuery -> m BigQuery #

Ord BigQuery # 
Instance details

Defined in Napkin.Types.BigQuery

Show BigQuery # 
Instance details

Defined in Napkin.Types.BigQuery

ReifiesBackend BigQuery # 
Instance details

Defined in Napkin.Types.BigQuery

Backend BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

Associated Types

data BackendConn BigQuery #

RunBackendConn BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

RunBackendEffect BigQuery # 
Instance details

Defined in Napkin.Run.Effects.Interpreters.Backend.BigQuery

Methods

runBackendEffectReal :: forall (r :: [(Type -> Type) -> Type -> Type]) a. (Members (Core BigQuery) r, Member (Embed IO) r) => BackendConn BigQuery -> Sem (BackendSpecificEffect BigQuery ': r) a -> Sem r a #

runBackendEffectFake :: forall (r :: [(Type -> Type) -> Type -> Type]) a. (Members (Core BigQuery) r, Member (Embed IO) r) => Sem (BackendSpecificEffect BigQuery ': r) a -> Sem r a #

RenderSql String BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Methods

renderSql :: BigQuery -> String -> Doc #

RenderSql Query BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Methods

renderSql :: BigQuery -> Query -> Doc #

RenderSql From BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Methods

renderSql :: BigQuery -> From -> Doc #

RenderSql Relation BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Methods

renderSql :: BigQuery -> Relation -> Doc #

RenderSql SExp BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Methods

renderSql :: BigQuery -> SExp -> Doc #

RenderSql Name BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Methods

renderSql :: BigQuery -> Name -> Doc #

RenderSql DeleteFrom BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

RenderSql InsertIntoQuery BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

RenderSql ML_Predict BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

RenderSql CreateModel BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

RenderSql ModelOptions BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

RenderSql ModelType BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Methods

renderSql :: BigQuery -> ModelType -> Doc #

RenderSql Replacement BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Command UpdateQuery () BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

Command Grant () BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

Command CheckTableExists Bool BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

Command DeleteFrom () BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

Command InsertIntoQuery () BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

Command DropTable () BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

Command DropView () BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

Command CopyTable () BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

Command RenameTable () BigQuery #

BQ implements rename via copy-then-drop

Instance details

Defined in Napkin.Run.BigQuery

Command GetRelationSchema [BackendSchemaField BigQuery] BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

Eq (DbBackendOptions BigQuery) # 
Instance details

Defined in Napkin.Run.BigQuery.Types

Show (DbBackendOptions BigQuery) # 
Instance details

Defined in Napkin.Run.BigQuery.Types

Generic (DbBackendOptions BigQuery) # 
Instance details

Defined in Napkin.Run.BigQuery.Types

Associated Types

type Rep (DbBackendOptions BigQuery) :: Type -> Type #

ToJSON (DbBackendOptions BigQuery) # 
Instance details

Defined in Napkin.Run.BigQuery.Types

ToJSON (YamlBackendTableMeta BigQuery) # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

FromJSON (DbBackendOptions BigQuery) # 
Instance details

Defined in Napkin.Run.BigQuery.Types

FromJSON (YamlBackendMaterializedViewMeta BigQuery) # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

FromJSON (YamlBackendViewMeta BigQuery) # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

FromJSON (YamlBackendTableMeta BigQuery) # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

Default (DbBackendOptions BigQuery) # 
Instance details

Defined in Napkin.Run.BigQuery.Types

MaybeDefault (YamlBackendMaterializedViewMeta BigQuery) # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

MaybeDefault (YamlBackendViewMeta BigQuery) # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

MaybeDefault (YamlBackendTableMeta BigQuery) # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

ToDbBackend BigQuery # 
Instance details

Defined in Napkin.Backends.Types

RenderSql a BigQuery => RenderSql (Alias a) BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Methods

renderSql :: BigQuery -> Alias a -> Doc #

RenderSql (CreateMaterializedViewAs MaterializedViewMeta) BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

RenderSql (CreateViewAs ()) BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Methods

renderSql :: BigQuery -> CreateViewAs () -> Doc #

RenderSql (CreateTableAs TableMeta) BigQuery #

Used for dump command only; BigQuery can create stuff via SQL, but for tables we are using API now

Instance details

Defined in Napkin.Render.BigQuery

HasBackendSchemaField BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

Associated Types

data BackendSchemaField BigQuery #

TardisCompat BigQuery # 
Instance details

Defined in Napkin.Experimental.Tardis

Command (CreateMaterializedViewAs MaterializedViewMeta) () BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

Command (CreateViewAs ()) () BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

Command (CreateTableAs ()) () BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

Command (CreateTableAs TableMeta) () BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

Eq (BackendSchemaField BigQuery) # 
Instance details

Defined in Napkin.Run.BigQuery

Show (BackendSchemaField BigQuery) # 
Instance details

Defined in Napkin.Run.BigQuery

RenderSql (Ref t) BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Methods

renderSql :: BigQuery -> Ref t -> Doc #

data BackendSpecificEffect BigQuery m a # 
Instance details

Defined in Napkin.Run.Effects.Languages.Backend.BigQuery

type BackendMaterializedViewMeta BigQuery # 
Instance details

Defined in Napkin.Types.BigQuery

type BackendViewMeta BigQuery # 
Instance details

Defined in Napkin.Types.BigQuery

type BackendTableMeta BigQuery # 
Instance details

Defined in Napkin.Types.BigQuery

data BackendConn BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

data DbBackendOptions BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery.Types

type Rep (DbBackendOptions BigQuery) # 
Instance details

Defined in Napkin.Run.BigQuery.Types

type Rep (DbBackendOptions BigQuery) = D1 ('MetaData "DbBackendOptions" "Napkin.Run.BigQuery.Types" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "BigQueryOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "_bigQueryOptions_labels") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Labels) :*: (S1 ('MetaSel ('Just "_bigQueryOptions_concurrentQueries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: S1 ('MetaSel ('Just "_bigQueryOptions_timeout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Seconds)))))
data BackendSchemaField BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

data BigQueryType #

Instances

Instances details
Eq BigQueryType # 
Instance details

Defined in Napkin.Types.BigQuery

Data BigQueryType # 
Instance details

Defined in Napkin.Types.BigQuery

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BigQueryType -> c BigQueryType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BigQueryType #

toConstr :: BigQueryType -> Constr #

dataTypeOf :: BigQueryType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BigQueryType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BigQueryType) #

gmapT :: (forall b. Data b => b -> b) -> BigQueryType -> BigQueryType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BigQueryType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BigQueryType -> r #

gmapQ :: (forall d. Data d => d -> u) -> BigQueryType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BigQueryType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BigQueryType -> m BigQueryType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BigQueryType -> m BigQueryType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BigQueryType -> m BigQueryType #

Ord BigQueryType # 
Instance details

Defined in Napkin.Types.BigQuery

Show BigQueryType # 
Instance details

Defined in Napkin.Types.BigQuery

data GCSBucket #

https://cloud.google.com/storage/docs/naming Between 3 and 63 chars, all lowercase, beginning and ending with alphanum, middle can contain alphanum or -,'_', and .. Avoid . in the bucket name as it requires verification. Also, common misspellings of google and IP addreses are not allowed but the risk of that seemed low so I omitted those rules.

Instances

Instances details
Eq GCSBucket # 
Instance details

Defined in Napkin.Types.BigQuery

Ord GCSBucket # 
Instance details

Defined in Napkin.Types.BigQuery

Show GCSBucket # 
Instance details

Defined in Napkin.Types.BigQuery

data GCSBucketNameError #

Omits rules about IP address bucket names or close misspellings of google.

data GCSKey #

https://cloud.google.com/storage/docs/naming No newlines, between 1 and 1024 chars

Instances

Instances details
Eq GCSKey # 
Instance details

Defined in Napkin.Types.BigQuery

Methods

(==) :: GCSKey -> GCSKey -> Bool #

(/=) :: GCSKey -> GCSKey -> Bool #

Ord GCSKey # 
Instance details

Defined in Napkin.Types.BigQuery

Show GCSKey # 
Instance details

Defined in Napkin.Types.BigQuery

data GCSKeyError #

Instances

Instances details
Eq GCSKeyError # 
Instance details

Defined in Napkin.Types.BigQuery

Show GCSKeyError # 
Instance details

Defined in Napkin.Types.BigQuery

data GCSACLEntity #

An entity which holds an ACL for an object or bucket in google cloud storage. I believe this means that whoever the entity targets can only hold one ACL, so you use this to do targeted/idempotent insertsreplacements of permissions on objectsbuckets.

newtype GCUserId #

Constructors

GCUserId 

Fields

Instances

Instances details
Eq GCUserId # 
Instance details

Defined in Napkin.Types.BigQuery

Ord GCUserId # 
Instance details

Defined in Napkin.Types.BigQuery

Show GCUserId # 
Instance details

Defined in Napkin.Types.BigQuery

newtype GCGroupId #

Constructors

GCGroupId 

Fields

Instances

Instances details
Eq GCGroupId # 
Instance details

Defined in Napkin.Types.BigQuery

Ord GCGroupId # 
Instance details

Defined in Napkin.Types.BigQuery

Show GCGroupId # 
Instance details

Defined in Napkin.Types.BigQuery

newtype GCDomain #

Constructors

GCDomain 

Fields

Instances

Instances details
Eq GCDomain # 
Instance details

Defined in Napkin.Types.BigQuery

Ord GCDomain # 
Instance details

Defined in Napkin.Types.BigQuery

Show GCDomain # 
Instance details

Defined in Napkin.Types.BigQuery

newtype GCTeam #

Constructors

GCTeam 

Fields

Instances

Instances details
Eq GCTeam # 
Instance details

Defined in Napkin.Types.BigQuery

Methods

(==) :: GCTeam -> GCTeam -> Bool #

(/=) :: GCTeam -> GCTeam -> Bool #

Ord GCTeam # 
Instance details

Defined in Napkin.Types.BigQuery

Show GCTeam # 
Instance details

Defined in Napkin.Types.BigQuery

data TableMeta #

Instances

Instances details
Eq TableMeta # 
Instance details

Defined in Napkin.Types.BigQuery

Data TableMeta # 
Instance details

Defined in Napkin.Types.BigQuery

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableMeta -> c TableMeta #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableMeta #

toConstr :: TableMeta -> Constr #

dataTypeOf :: TableMeta -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableMeta) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableMeta) #

gmapT :: (forall b. Data b => b -> b) -> TableMeta -> TableMeta #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableMeta -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableMeta -> r #

gmapQ :: (forall d. Data d => d -> u) -> TableMeta -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TableMeta -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableMeta -> m TableMeta #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableMeta -> m TableMeta #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableMeta -> m TableMeta #

Show TableMeta # 
Instance details

Defined in Napkin.Types.BigQuery

Generic TableMeta # 
Instance details

Defined in Napkin.Types.BigQuery

Associated Types

type Rep TableMeta :: Type -> Type #

Default TableMeta # 
Instance details

Defined in Napkin.Types.BigQuery

Methods

def :: TableMeta #

RenderSql (CreateTableAs TableMeta) BigQuery #

Used for dump command only; BigQuery can create stuff via SQL, but for tables we are using API now

Instance details

Defined in Napkin.Render.BigQuery

Command (CreateTableAs TableMeta) () BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

type Rep TableMeta # 
Instance details

Defined in Napkin.Types.BigQuery

type Rep TableMeta = D1 ('MetaData "TableMeta" "Napkin.Types.BigQuery" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "TableMeta" 'PrefixI 'True) (S1 ('MetaSel ('Just "_tableMeta_partitioning") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TablePartitioning)) :*: (S1 ('MetaSel ('Just "_tableMeta_clustering") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Clustering)) :*: S1 ('MetaSel ('Just "_tableMeta_writeDisposition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe WriteDisposition)))))

data TablePartitioning #

Instances

Instances details
Eq TablePartitioning # 
Instance details

Defined in Napkin.Types.BigQuery

Data TablePartitioning # 
Instance details

Defined in Napkin.Types.BigQuery

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TablePartitioning -> c TablePartitioning #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TablePartitioning #

toConstr :: TablePartitioning -> Constr #

dataTypeOf :: TablePartitioning -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TablePartitioning) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TablePartitioning) #

gmapT :: (forall b. Data b => b -> b) -> TablePartitioning -> TablePartitioning #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TablePartitioning -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TablePartitioning -> r #

gmapQ :: (forall d. Data d => d -> u) -> TablePartitioning -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TablePartitioning -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TablePartitioning -> m TablePartitioning #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TablePartitioning -> m TablePartitioning #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TablePartitioning -> m TablePartitioning #

Show TablePartitioning # 
Instance details

Defined in Napkin.Types.BigQuery

Generic TablePartitioning # 
Instance details

Defined in Napkin.Types.BigQuery

Associated Types

type Rep TablePartitioning :: Type -> Type #

ToJSON TablePartitioning # 
Instance details

Defined in Napkin.Types.BigQuery

FromJSON TablePartitioning # 
Instance details

Defined in Napkin.Types.BigQuery

type Rep TablePartitioning # 
Instance details

Defined in Napkin.Types.BigQuery

data WriteDisposition #

Instances

Instances details
Eq WriteDisposition # 
Instance details

Defined in Napkin.Types.BigQuery

Data WriteDisposition # 
Instance details

Defined in Napkin.Types.BigQuery

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WriteDisposition -> c WriteDisposition #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WriteDisposition #

toConstr :: WriteDisposition -> Constr #

dataTypeOf :: WriteDisposition -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WriteDisposition) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WriteDisposition) #

gmapT :: (forall b. Data b => b -> b) -> WriteDisposition -> WriteDisposition #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WriteDisposition -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WriteDisposition -> r #

gmapQ :: (forall d. Data d => d -> u) -> WriteDisposition -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WriteDisposition -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WriteDisposition -> m WriteDisposition #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WriteDisposition -> m WriteDisposition #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WriteDisposition -> m WriteDisposition #

Ord WriteDisposition # 
Instance details

Defined in Napkin.Types.BigQuery

Show WriteDisposition # 
Instance details

Defined in Napkin.Types.BigQuery

Generic WriteDisposition # 
Instance details

Defined in Napkin.Types.BigQuery

Associated Types

type Rep WriteDisposition :: Type -> Type #

ToJSON WriteDisposition # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

FromJSON WriteDisposition # 
Instance details

Defined in Napkin.Spec.Yaml.Types.BackendMeta

type Rep WriteDisposition # 
Instance details

Defined in Napkin.Types.BigQuery

type Rep WriteDisposition = D1 ('MetaData "WriteDisposition" "Napkin.Types.BigQuery" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "WriteDisposition_WriteEmpty" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WriteDisposition_WriteAppend" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WriteDisposition_WriteTruncate" 'PrefixI 'False) (U1 :: Type -> Type)))

data MaterializedViewMeta #

Instances

Instances details
Eq MaterializedViewMeta # 
Instance details

Defined in Napkin.Types.BigQuery

Show MaterializedViewMeta # 
Instance details

Defined in Napkin.Types.BigQuery

Generic MaterializedViewMeta # 
Instance details

Defined in Napkin.Types.BigQuery

Associated Types

type Rep MaterializedViewMeta :: Type -> Type #

ToJSON MaterializedViewMeta # 
Instance details

Defined in Napkin.Types.BigQuery

FromJSON MaterializedViewMeta # 
Instance details

Defined in Napkin.Types.BigQuery

Default MaterializedViewMeta # 
Instance details

Defined in Napkin.Types.BigQuery

RenderSql (CreateMaterializedViewAs MaterializedViewMeta) BigQuery # 
Instance details

Defined in Napkin.Render.BigQuery

Command (CreateMaterializedViewAs MaterializedViewMeta) () BigQuery # 
Instance details

Defined in Napkin.Run.BigQuery

type Rep MaterializedViewMeta # 
Instance details

Defined in Napkin.Types.BigQuery

type Rep MaterializedViewMeta = D1 ('MetaData "MaterializedViewMeta" "Napkin.Types.BigQuery" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "MaterializedViewMeta" 'PrefixI 'True) (S1 ('MetaSel ('Just "_materializedViewMeta_partitioning") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TablePartitioning)) :*: (S1 ('MetaSel ('Just "_materializedViewMeta_clustering") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Clustering)) :*: S1 ('MetaSel ('Just "_materializedViewMeta_refresh") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MaterializedViewRefresh)))))

data RangeWithStep #

Instances

Instances details
Eq RangeWithStep # 
Instance details

Defined in Napkin.Types.BigQuery

Data RangeWithStep # 
Instance details

Defined in Napkin.Types.BigQuery

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RangeWithStep -> c RangeWithStep #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RangeWithStep #

toConstr :: RangeWithStep -> Constr #

dataTypeOf :: RangeWithStep -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RangeWithStep) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RangeWithStep) #

gmapT :: (forall b. Data b => b -> b) -> RangeWithStep -> RangeWithStep #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RangeWithStep -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RangeWithStep -> r #

gmapQ :: (forall d. Data d => d -> u) -> RangeWithStep -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RangeWithStep -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RangeWithStep -> m RangeWithStep #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RangeWithStep -> m RangeWithStep #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RangeWithStep -> m RangeWithStep #

Show RangeWithStep # 
Instance details

Defined in Napkin.Types.BigQuery

Generic RangeWithStep # 
Instance details

Defined in Napkin.Types.BigQuery

Associated Types

type Rep RangeWithStep :: Type -> Type #

ToJSON RangeWithStep # 
Instance details

Defined in Napkin.Types.BigQuery

FromJSON RangeWithStep # 
Instance details

Defined in Napkin.Types.BigQuery

type Rep RangeWithStep # 
Instance details

Defined in Napkin.Types.BigQuery

type Rep RangeWithStep = D1 ('MetaData "RangeWithStep" "Napkin.Types.BigQuery" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "RangeWithStep" 'PrefixI 'True) (S1 ('MetaSel ('Just "_rangeStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64) :*: (S1 ('MetaSel ('Just "_rangeEnd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64) :*: S1 ('MetaSel ('Just "_rangeStep") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64))))

data MaterializedViewRefresh #

Instances

Instances details
Eq MaterializedViewRefresh # 
Instance details

Defined in Napkin.Types.BigQuery

Show MaterializedViewRefresh # 
Instance details

Defined in Napkin.Types.BigQuery

Generic MaterializedViewRefresh # 
Instance details

Defined in Napkin.Types.BigQuery

Associated Types

type Rep MaterializedViewRefresh :: Type -> Type #

ToJSON MaterializedViewRefresh # 
Instance details

Defined in Napkin.Types.BigQuery

FromJSON MaterializedViewRefresh # 
Instance details

Defined in Napkin.Types.BigQuery

type Rep MaterializedViewRefresh # 
Instance details

Defined in Napkin.Types.BigQuery

type Rep MaterializedViewRefresh = D1 ('MetaData "MaterializedViewRefresh" "Napkin.Types.BigQuery" "napkin-0.5.13-8705pBGlgyp7AIaYGNE2fM" 'False) (C1 ('MetaCons "Refresh_Automatic" 'PrefixI 'True) (S1 ('MetaSel ('Just "_refresh_minutes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)) :+: C1 ('MetaCons "Refresh_Manual" 'PrefixI 'False) (U1 :: Type -> Type))

refComponents :: Ref a -> (Name, Name, Name) #

Deconstruct a Ref into project, dataset, and table name components.