{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric      #-}
{-# LANGUAGE NoImplicitPrelude  #-}
{-# LANGUAGE OverloadedStrings  #-}
{-# LANGUAGE RecordWildCards    #-}
{-# OPTIONS_GHC -fno-warn-unused-binds   #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Network.Google.BigQuery.Types.Product where
import           Network.Google.BigQuery.Types.Sum
import           Network.Google.Prelude
data JobReference =
  JobReference'
    { _jrJobId     :: !(Maybe Text)
    , _jrLocation  :: !(Maybe Text)
    , _jrProjectId :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobReference
    :: JobReference
jobReference =
  JobReference'
    {_jrJobId = Nothing, _jrLocation = Nothing, _jrProjectId = Nothing}
jrJobId :: Lens' JobReference (Maybe Text)
jrJobId = lens _jrJobId (\ s a -> s{_jrJobId = a})
jrLocation :: Lens' JobReference (Maybe Text)
jrLocation
  = lens _jrLocation (\ s a -> s{_jrLocation = a})
jrProjectId :: Lens' JobReference (Maybe Text)
jrProjectId
  = lens _jrProjectId (\ s a -> s{_jrProjectId = a})
instance FromJSON JobReference where
        parseJSON
          = withObject "JobReference"
              (\ o ->
                 JobReference' <$>
                   (o .:? "jobId") <*> (o .:? "location") <*>
                     (o .:? "projectId"))
instance ToJSON JobReference where
        toJSON JobReference'{..}
          = object
              (catMaybes
                 [("jobId" .=) <$> _jrJobId,
                  ("location" .=) <$> _jrLocation,
                  ("projectId" .=) <$> _jrProjectId])
data TableList =
  TableList'
    { _tlTotalItems    :: !(Maybe (Textual Int32))
    , _tlEtag          :: !(Maybe Text)
    , _tlNextPageToken :: !(Maybe Text)
    , _tlKind          :: !Text
    , _tlTables        :: !(Maybe [TableListTablesItem])
    }
  deriving (Eq, Show, Data, Typeable, Generic)
tableList
    :: TableList
tableList =
  TableList'
    { _tlTotalItems = Nothing
    , _tlEtag = Nothing
    , _tlNextPageToken = Nothing
    , _tlKind = "bigquery#tableList"
    , _tlTables = Nothing
    }
tlTotalItems :: Lens' TableList (Maybe Int32)
tlTotalItems
  = lens _tlTotalItems (\ s a -> s{_tlTotalItems = a})
      . mapping _Coerce
tlEtag :: Lens' TableList (Maybe Text)
tlEtag = lens _tlEtag (\ s a -> s{_tlEtag = a})
tlNextPageToken :: Lens' TableList (Maybe Text)
tlNextPageToken
  = lens _tlNextPageToken
      (\ s a -> s{_tlNextPageToken = a})
tlKind :: Lens' TableList Text
tlKind = lens _tlKind (\ s a -> s{_tlKind = a})
tlTables :: Lens' TableList [TableListTablesItem]
tlTables
  = lens _tlTables (\ s a -> s{_tlTables = a}) .
      _Default
      . _Coerce
instance FromJSON TableList where
        parseJSON
          = withObject "TableList"
              (\ o ->
                 TableList' <$>
                   (o .:? "totalItems") <*> (o .:? "etag") <*>
                     (o .:? "nextPageToken")
                     <*> (o .:? "kind" .!= "bigquery#tableList")
                     <*> (o .:? "tables" .!= mempty))
instance ToJSON TableList where
        toJSON TableList'{..}
          = object
              (catMaybes
                 [("totalItems" .=) <$> _tlTotalItems,
                  ("etag" .=) <$> _tlEtag,
                  ("nextPageToken" .=) <$> _tlNextPageToken,
                  Just ("kind" .= _tlKind),
                  ("tables" .=) <$> _tlTables])
data DataSetListDataSetsItem =
  DataSetListDataSetsItem'
    { _dsldsiLocation         :: !(Maybe Text)
    , _dsldsiFriendlyName     :: !(Maybe Text)
    , _dsldsiKind             :: !Text
    , _dsldsiDataSetReference :: !(Maybe DataSetReference)
    , _dsldsiId               :: !(Maybe Text)
    , _dsldsiLabels           :: !(Maybe DataSetListDataSetsItemLabels)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
dataSetListDataSetsItem
    :: DataSetListDataSetsItem
dataSetListDataSetsItem =
  DataSetListDataSetsItem'
    { _dsldsiLocation = Nothing
    , _dsldsiFriendlyName = Nothing
    , _dsldsiKind = "bigquery#dataset"
    , _dsldsiDataSetReference = Nothing
    , _dsldsiId = Nothing
    , _dsldsiLabels = Nothing
    }
dsldsiLocation :: Lens' DataSetListDataSetsItem (Maybe Text)
dsldsiLocation
  = lens _dsldsiLocation
      (\ s a -> s{_dsldsiLocation = a})
dsldsiFriendlyName :: Lens' DataSetListDataSetsItem (Maybe Text)
dsldsiFriendlyName
  = lens _dsldsiFriendlyName
      (\ s a -> s{_dsldsiFriendlyName = a})
dsldsiKind :: Lens' DataSetListDataSetsItem Text
dsldsiKind
  = lens _dsldsiKind (\ s a -> s{_dsldsiKind = a})
dsldsiDataSetReference :: Lens' DataSetListDataSetsItem (Maybe DataSetReference)
dsldsiDataSetReference
  = lens _dsldsiDataSetReference
      (\ s a -> s{_dsldsiDataSetReference = a})
dsldsiId :: Lens' DataSetListDataSetsItem (Maybe Text)
dsldsiId = lens _dsldsiId (\ s a -> s{_dsldsiId = a})
dsldsiLabels :: Lens' DataSetListDataSetsItem (Maybe DataSetListDataSetsItemLabels)
dsldsiLabels
  = lens _dsldsiLabels (\ s a -> s{_dsldsiLabels = a})
instance FromJSON DataSetListDataSetsItem where
        parseJSON
          = withObject "DataSetListDataSetsItem"
              (\ o ->
                 DataSetListDataSetsItem' <$>
                   (o .:? "location") <*> (o .:? "friendlyName") <*>
                     (o .:? "kind" .!= "bigquery#dataset")
                     <*> (o .:? "datasetReference")
                     <*> (o .:? "id")
                     <*> (o .:? "labels"))
instance ToJSON DataSetListDataSetsItem where
        toJSON DataSetListDataSetsItem'{..}
          = object
              (catMaybes
                 [("location" .=) <$> _dsldsiLocation,
                  ("friendlyName" .=) <$> _dsldsiFriendlyName,
                  Just ("kind" .= _dsldsiKind),
                  ("datasetReference" .=) <$> _dsldsiDataSetReference,
                  ("id" .=) <$> _dsldsiId,
                  ("labels" .=) <$> _dsldsiLabels])
data TableDataList =
  TableDataList'
    { _tdlEtag      :: !(Maybe Text)
    , _tdlKind      :: !Text
    , _tdlRows      :: !(Maybe [TableRow])
    , _tdlPageToken :: !(Maybe Text)
    , _tdlTotalRows :: !(Maybe (Textual Int64))
    }
  deriving (Eq, Show, Data, Typeable, Generic)
tableDataList
    :: TableDataList
tableDataList =
  TableDataList'
    { _tdlEtag = Nothing
    , _tdlKind = "bigquery#tableDataList"
    , _tdlRows = Nothing
    , _tdlPageToken = Nothing
    , _tdlTotalRows = Nothing
    }
tdlEtag :: Lens' TableDataList (Maybe Text)
tdlEtag = lens _tdlEtag (\ s a -> s{_tdlEtag = a})
tdlKind :: Lens' TableDataList Text
tdlKind = lens _tdlKind (\ s a -> s{_tdlKind = a})
tdlRows :: Lens' TableDataList [TableRow]
tdlRows
  = lens _tdlRows (\ s a -> s{_tdlRows = a}) . _Default
      . _Coerce
tdlPageToken :: Lens' TableDataList (Maybe Text)
tdlPageToken
  = lens _tdlPageToken (\ s a -> s{_tdlPageToken = a})
tdlTotalRows :: Lens' TableDataList (Maybe Int64)
tdlTotalRows
  = lens _tdlTotalRows (\ s a -> s{_tdlTotalRows = a})
      . mapping _Coerce
instance FromJSON TableDataList where
        parseJSON
          = withObject "TableDataList"
              (\ o ->
                 TableDataList' <$>
                   (o .:? "etag") <*>
                     (o .:? "kind" .!= "bigquery#tableDataList")
                     <*> (o .:? "rows" .!= mempty)
                     <*> (o .:? "pageToken")
                     <*> (o .:? "totalRows"))
instance ToJSON TableDataList where
        toJSON TableDataList'{..}
          = object
              (catMaybes
                 [("etag" .=) <$> _tdlEtag, Just ("kind" .= _tdlKind),
                  ("rows" .=) <$> _tdlRows,
                  ("pageToken" .=) <$> _tdlPageToken,
                  ("totalRows" .=) <$> _tdlTotalRows])
data JobConfigurationTableCopy =
  JobConfigurationTableCopy'
    { _jctcDestinationTable                   :: !(Maybe TableReference)
    , _jctcWriteDisPosition                   :: !(Maybe Text)
    , _jctcSourceTables                       :: !(Maybe [TableReference])
    , _jctcCreateDisPosition                  :: !(Maybe Text)
    , _jctcSourceTable                        :: !(Maybe TableReference)
    , _jctcDestinationEncryptionConfiguration :: !(Maybe EncryptionConfiguration)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobConfigurationTableCopy
    :: JobConfigurationTableCopy
jobConfigurationTableCopy =
  JobConfigurationTableCopy'
    { _jctcDestinationTable = Nothing
    , _jctcWriteDisPosition = Nothing
    , _jctcSourceTables = Nothing
    , _jctcCreateDisPosition = Nothing
    , _jctcSourceTable = Nothing
    , _jctcDestinationEncryptionConfiguration = Nothing
    }
jctcDestinationTable :: Lens' JobConfigurationTableCopy (Maybe TableReference)
jctcDestinationTable
  = lens _jctcDestinationTable
      (\ s a -> s{_jctcDestinationTable = a})
jctcWriteDisPosition :: Lens' JobConfigurationTableCopy (Maybe Text)
jctcWriteDisPosition
  = lens _jctcWriteDisPosition
      (\ s a -> s{_jctcWriteDisPosition = a})
jctcSourceTables :: Lens' JobConfigurationTableCopy [TableReference]
jctcSourceTables
  = lens _jctcSourceTables
      (\ s a -> s{_jctcSourceTables = a})
      . _Default
      . _Coerce
jctcCreateDisPosition :: Lens' JobConfigurationTableCopy (Maybe Text)
jctcCreateDisPosition
  = lens _jctcCreateDisPosition
      (\ s a -> s{_jctcCreateDisPosition = a})
jctcSourceTable :: Lens' JobConfigurationTableCopy (Maybe TableReference)
jctcSourceTable
  = lens _jctcSourceTable
      (\ s a -> s{_jctcSourceTable = a})
jctcDestinationEncryptionConfiguration :: Lens' JobConfigurationTableCopy (Maybe EncryptionConfiguration)
jctcDestinationEncryptionConfiguration
  = lens _jctcDestinationEncryptionConfiguration
      (\ s a ->
         s{_jctcDestinationEncryptionConfiguration = a})
instance FromJSON JobConfigurationTableCopy where
        parseJSON
          = withObject "JobConfigurationTableCopy"
              (\ o ->
                 JobConfigurationTableCopy' <$>
                   (o .:? "destinationTable") <*>
                     (o .:? "writeDisposition")
                     <*> (o .:? "sourceTables" .!= mempty)
                     <*> (o .:? "createDisposition")
                     <*> (o .:? "sourceTable")
                     <*> (o .:? "destinationEncryptionConfiguration"))
instance ToJSON JobConfigurationTableCopy where
        toJSON JobConfigurationTableCopy'{..}
          = object
              (catMaybes
                 [("destinationTable" .=) <$> _jctcDestinationTable,
                  ("writeDisposition" .=) <$> _jctcWriteDisPosition,
                  ("sourceTables" .=) <$> _jctcSourceTables,
                  ("createDisposition" .=) <$> _jctcCreateDisPosition,
                  ("sourceTable" .=) <$> _jctcSourceTable,
                  ("destinationEncryptionConfiguration" .=) <$>
                    _jctcDestinationEncryptionConfiguration])
data TableListTablesItem =
  TableListTablesItem'
    { _tltiCreationTime     :: !(Maybe (Textual Int64))
    , _tltiClustering       :: !(Maybe Clustering)
    , _tltiTableReference   :: !(Maybe TableReference)
    , _tltiFriendlyName     :: !(Maybe Text)
    , _tltiKind             :: !Text
    , _tltiTimePartitioning :: !(Maybe TimePartitioning)
    , _tltiView             :: !(Maybe TableListTablesItemView)
    , _tltiId               :: !(Maybe Text)
    , _tltiLabels           :: !(Maybe TableListTablesItemLabels)
    , _tltiType             :: !(Maybe Text)
    , _tltiExpirationTime   :: !(Maybe (Textual Int64))
    }
  deriving (Eq, Show, Data, Typeable, Generic)
tableListTablesItem
    :: TableListTablesItem
tableListTablesItem =
  TableListTablesItem'
    { _tltiCreationTime = Nothing
    , _tltiClustering = Nothing
    , _tltiTableReference = Nothing
    , _tltiFriendlyName = Nothing
    , _tltiKind = "bigquery#table"
    , _tltiTimePartitioning = Nothing
    , _tltiView = Nothing
    , _tltiId = Nothing
    , _tltiLabels = Nothing
    , _tltiType = Nothing
    , _tltiExpirationTime = Nothing
    }
tltiCreationTime :: Lens' TableListTablesItem (Maybe Int64)
tltiCreationTime
  = lens _tltiCreationTime
      (\ s a -> s{_tltiCreationTime = a})
      . mapping _Coerce
tltiClustering :: Lens' TableListTablesItem (Maybe Clustering)
tltiClustering
  = lens _tltiClustering
      (\ s a -> s{_tltiClustering = a})
tltiTableReference :: Lens' TableListTablesItem (Maybe TableReference)
tltiTableReference
  = lens _tltiTableReference
      (\ s a -> s{_tltiTableReference = a})
tltiFriendlyName :: Lens' TableListTablesItem (Maybe Text)
tltiFriendlyName
  = lens _tltiFriendlyName
      (\ s a -> s{_tltiFriendlyName = a})
tltiKind :: Lens' TableListTablesItem Text
tltiKind = lens _tltiKind (\ s a -> s{_tltiKind = a})
tltiTimePartitioning :: Lens' TableListTablesItem (Maybe TimePartitioning)
tltiTimePartitioning
  = lens _tltiTimePartitioning
      (\ s a -> s{_tltiTimePartitioning = a})
tltiView :: Lens' TableListTablesItem (Maybe TableListTablesItemView)
tltiView = lens _tltiView (\ s a -> s{_tltiView = a})
tltiId :: Lens' TableListTablesItem (Maybe Text)
tltiId = lens _tltiId (\ s a -> s{_tltiId = a})
tltiLabels :: Lens' TableListTablesItem (Maybe TableListTablesItemLabels)
tltiLabels
  = lens _tltiLabels (\ s a -> s{_tltiLabels = a})
tltiType :: Lens' TableListTablesItem (Maybe Text)
tltiType = lens _tltiType (\ s a -> s{_tltiType = a})
tltiExpirationTime :: Lens' TableListTablesItem (Maybe Int64)
tltiExpirationTime
  = lens _tltiExpirationTime
      (\ s a -> s{_tltiExpirationTime = a})
      . mapping _Coerce
instance FromJSON TableListTablesItem where
        parseJSON
          = withObject "TableListTablesItem"
              (\ o ->
                 TableListTablesItem' <$>
                   (o .:? "creationTime") <*> (o .:? "clustering") <*>
                     (o .:? "tableReference")
                     <*> (o .:? "friendlyName")
                     <*> (o .:? "kind" .!= "bigquery#table")
                     <*> (o .:? "timePartitioning")
                     <*> (o .:? "view")
                     <*> (o .:? "id")
                     <*> (o .:? "labels")
                     <*> (o .:? "type")
                     <*> (o .:? "expirationTime"))
instance ToJSON TableListTablesItem where
        toJSON TableListTablesItem'{..}
          = object
              (catMaybes
                 [("creationTime" .=) <$> _tltiCreationTime,
                  ("clustering" .=) <$> _tltiClustering,
                  ("tableReference" .=) <$> _tltiTableReference,
                  ("friendlyName" .=) <$> _tltiFriendlyName,
                  Just ("kind" .= _tltiKind),
                  ("timePartitioning" .=) <$> _tltiTimePartitioning,
                  ("view" .=) <$> _tltiView, ("id" .=) <$> _tltiId,
                  ("labels" .=) <$> _tltiLabels,
                  ("type" .=) <$> _tltiType,
                  ("expirationTime" .=) <$> _tltiExpirationTime])
newtype TableSchema =
  TableSchema'
    { _tsFields :: Maybe [TableFieldSchema]
    }
  deriving (Eq, Show, Data, Typeable, Generic)
tableSchema
    :: TableSchema
tableSchema = TableSchema' {_tsFields = Nothing}
tsFields :: Lens' TableSchema [TableFieldSchema]
tsFields
  = lens _tsFields (\ s a -> s{_tsFields = a}) .
      _Default
      . _Coerce
instance FromJSON TableSchema where
        parseJSON
          = withObject "TableSchema"
              (\ o -> TableSchema' <$> (o .:? "fields" .!= mempty))
instance ToJSON TableSchema where
        toJSON TableSchema'{..}
          = object (catMaybes [("fields" .=) <$> _tsFields])
data ProjectList =
  ProjectList'
    { _plTotalItems    :: !(Maybe (Textual Int32))
    , _plEtag          :: !(Maybe Text)
    , _plNextPageToken :: !(Maybe Text)
    , _plKind          :: !Text
    , _plProjects      :: !(Maybe [ProjectListProjectsItem])
    }
  deriving (Eq, Show, Data, Typeable, Generic)
projectList
    :: ProjectList
projectList =
  ProjectList'
    { _plTotalItems = Nothing
    , _plEtag = Nothing
    , _plNextPageToken = Nothing
    , _plKind = "bigquery#projectList"
    , _plProjects = Nothing
    }
plTotalItems :: Lens' ProjectList (Maybe Int32)
plTotalItems
  = lens _plTotalItems (\ s a -> s{_plTotalItems = a})
      . mapping _Coerce
plEtag :: Lens' ProjectList (Maybe Text)
plEtag = lens _plEtag (\ s a -> s{_plEtag = a})
plNextPageToken :: Lens' ProjectList (Maybe Text)
plNextPageToken
  = lens _plNextPageToken
      (\ s a -> s{_plNextPageToken = a})
plKind :: Lens' ProjectList Text
plKind = lens _plKind (\ s a -> s{_plKind = a})
plProjects :: Lens' ProjectList [ProjectListProjectsItem]
plProjects
  = lens _plProjects (\ s a -> s{_plProjects = a}) .
      _Default
      . _Coerce
instance FromJSON ProjectList where
        parseJSON
          = withObject "ProjectList"
              (\ o ->
                 ProjectList' <$>
                   (o .:? "totalItems") <*> (o .:? "etag") <*>
                     (o .:? "nextPageToken")
                     <*> (o .:? "kind" .!= "bigquery#projectList")
                     <*> (o .:? "projects" .!= mempty))
instance ToJSON ProjectList where
        toJSON ProjectList'{..}
          = object
              (catMaybes
                 [("totalItems" .=) <$> _plTotalItems,
                  ("etag" .=) <$> _plEtag,
                  ("nextPageToken" .=) <$> _plNextPageToken,
                  Just ("kind" .= _plKind),
                  ("projects" .=) <$> _plProjects])
data ExplainQueryStep =
  ExplainQueryStep'
    { _eqsSubsteps :: !(Maybe [Text])
    , _eqsKind     :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
explainQueryStep
    :: ExplainQueryStep
explainQueryStep =
  ExplainQueryStep' {_eqsSubsteps = Nothing, _eqsKind = Nothing}
eqsSubsteps :: Lens' ExplainQueryStep [Text]
eqsSubsteps
  = lens _eqsSubsteps (\ s a -> s{_eqsSubsteps = a}) .
      _Default
      . _Coerce
eqsKind :: Lens' ExplainQueryStep (Maybe Text)
eqsKind = lens _eqsKind (\ s a -> s{_eqsKind = a})
instance FromJSON ExplainQueryStep where
        parseJSON
          = withObject "ExplainQueryStep"
              (\ o ->
                 ExplainQueryStep' <$>
                   (o .:? "substeps" .!= mempty) <*> (o .:? "kind"))
instance ToJSON ExplainQueryStep where
        toJSON ExplainQueryStep'{..}
          = object
              (catMaybes
                 [("substeps" .=) <$> _eqsSubsteps,
                  ("kind" .=) <$> _eqsKind])
data QueryTimelineSample =
  QueryTimelineSample'
    { _qtsPendingUnits   :: !(Maybe (Textual Int64))
    , _qtsTotalSlotMs    :: !(Maybe (Textual Int64))
    , _qtsActiveUnits    :: !(Maybe (Textual Int64))
    , _qtsElapsedMs      :: !(Maybe (Textual Int64))
    , _qtsCompletedUnits :: !(Maybe (Textual Int64))
    }
  deriving (Eq, Show, Data, Typeable, Generic)
queryTimelineSample
    :: QueryTimelineSample
queryTimelineSample =
  QueryTimelineSample'
    { _qtsPendingUnits = Nothing
    , _qtsTotalSlotMs = Nothing
    , _qtsActiveUnits = Nothing
    , _qtsElapsedMs = Nothing
    , _qtsCompletedUnits = Nothing
    }
qtsPendingUnits :: Lens' QueryTimelineSample (Maybe Int64)
qtsPendingUnits
  = lens _qtsPendingUnits
      (\ s a -> s{_qtsPendingUnits = a})
      . mapping _Coerce
qtsTotalSlotMs :: Lens' QueryTimelineSample (Maybe Int64)
qtsTotalSlotMs
  = lens _qtsTotalSlotMs
      (\ s a -> s{_qtsTotalSlotMs = a})
      . mapping _Coerce
qtsActiveUnits :: Lens' QueryTimelineSample (Maybe Int64)
qtsActiveUnits
  = lens _qtsActiveUnits
      (\ s a -> s{_qtsActiveUnits = a})
      . mapping _Coerce
qtsElapsedMs :: Lens' QueryTimelineSample (Maybe Int64)
qtsElapsedMs
  = lens _qtsElapsedMs (\ s a -> s{_qtsElapsedMs = a})
      . mapping _Coerce
qtsCompletedUnits :: Lens' QueryTimelineSample (Maybe Int64)
qtsCompletedUnits
  = lens _qtsCompletedUnits
      (\ s a -> s{_qtsCompletedUnits = a})
      . mapping _Coerce
instance FromJSON QueryTimelineSample where
        parseJSON
          = withObject "QueryTimelineSample"
              (\ o ->
                 QueryTimelineSample' <$>
                   (o .:? "pendingUnits") <*> (o .:? "totalSlotMs") <*>
                     (o .:? "activeUnits")
                     <*> (o .:? "elapsedMs")
                     <*> (o .:? "completedUnits"))
instance ToJSON QueryTimelineSample where
        toJSON QueryTimelineSample'{..}
          = object
              (catMaybes
                 [("pendingUnits" .=) <$> _qtsPendingUnits,
                  ("totalSlotMs" .=) <$> _qtsTotalSlotMs,
                  ("activeUnits" .=) <$> _qtsActiveUnits,
                  ("elapsedMs" .=) <$> _qtsElapsedMs,
                  ("completedUnits" .=) <$> _qtsCompletedUnits])
data QueryParameterTypeStructTypesItem =
  QueryParameterTypeStructTypesItem'
    { _qptstiName        :: !(Maybe Text)
    , _qptstiType        :: !(Maybe QueryParameterType)
    , _qptstiDescription :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
queryParameterTypeStructTypesItem
    :: QueryParameterTypeStructTypesItem
queryParameterTypeStructTypesItem =
  QueryParameterTypeStructTypesItem'
    {_qptstiName = Nothing, _qptstiType = Nothing, _qptstiDescription = Nothing}
qptstiName :: Lens' QueryParameterTypeStructTypesItem (Maybe Text)
qptstiName
  = lens _qptstiName (\ s a -> s{_qptstiName = a})
qptstiType :: Lens' QueryParameterTypeStructTypesItem (Maybe QueryParameterType)
qptstiType
  = lens _qptstiType (\ s a -> s{_qptstiType = a})
qptstiDescription :: Lens' QueryParameterTypeStructTypesItem (Maybe Text)
qptstiDescription
  = lens _qptstiDescription
      (\ s a -> s{_qptstiDescription = a})
instance FromJSON QueryParameterTypeStructTypesItem
         where
        parseJSON
          = withObject "QueryParameterTypeStructTypesItem"
              (\ o ->
                 QueryParameterTypeStructTypesItem' <$>
                   (o .:? "name") <*> (o .:? "type") <*>
                     (o .:? "description"))
instance ToJSON QueryParameterTypeStructTypesItem
         where
        toJSON QueryParameterTypeStructTypesItem'{..}
          = object
              (catMaybes
                 [("name" .=) <$> _qptstiName,
                  ("type" .=) <$> _qptstiType,
                  ("description" .=) <$> _qptstiDescription])
data BigtableColumnFamily =
  BigtableColumnFamily'
    { _bcfFamilyId       :: !(Maybe Text)
    , _bcfColumns        :: !(Maybe [BigtableColumn])
    , _bcfOnlyReadLatest :: !(Maybe Bool)
    , _bcfType           :: !(Maybe Text)
    , _bcfEncoding       :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
bigtableColumnFamily
    :: BigtableColumnFamily
bigtableColumnFamily =
  BigtableColumnFamily'
    { _bcfFamilyId = Nothing
    , _bcfColumns = Nothing
    , _bcfOnlyReadLatest = Nothing
    , _bcfType = Nothing
    , _bcfEncoding = Nothing
    }
bcfFamilyId :: Lens' BigtableColumnFamily (Maybe Text)
bcfFamilyId
  = lens _bcfFamilyId (\ s a -> s{_bcfFamilyId = a})
bcfColumns :: Lens' BigtableColumnFamily [BigtableColumn]
bcfColumns
  = lens _bcfColumns (\ s a -> s{_bcfColumns = a}) .
      _Default
      . _Coerce
bcfOnlyReadLatest :: Lens' BigtableColumnFamily (Maybe Bool)
bcfOnlyReadLatest
  = lens _bcfOnlyReadLatest
      (\ s a -> s{_bcfOnlyReadLatest = a})
bcfType :: Lens' BigtableColumnFamily (Maybe Text)
bcfType = lens _bcfType (\ s a -> s{_bcfType = a})
bcfEncoding :: Lens' BigtableColumnFamily (Maybe Text)
bcfEncoding
  = lens _bcfEncoding (\ s a -> s{_bcfEncoding = a})
instance FromJSON BigtableColumnFamily where
        parseJSON
          = withObject "BigtableColumnFamily"
              (\ o ->
                 BigtableColumnFamily' <$>
                   (o .:? "familyId") <*> (o .:? "columns" .!= mempty)
                     <*> (o .:? "onlyReadLatest")
                     <*> (o .:? "type")
                     <*> (o .:? "encoding"))
instance ToJSON BigtableColumnFamily where
        toJSON BigtableColumnFamily'{..}
          = object
              (catMaybes
                 [("familyId" .=) <$> _bcfFamilyId,
                  ("columns" .=) <$> _bcfColumns,
                  ("onlyReadLatest" .=) <$> _bcfOnlyReadLatest,
                  ("type" .=) <$> _bcfType,
                  ("encoding" .=) <$> _bcfEncoding])
data JobStatistics =
  JobStatistics'
    { _jsCreationTime        :: !(Maybe (Textual Int64))
    , _jsStartTime           :: !(Maybe (Textual Int64))
    , _jsCompletionRatio     :: !(Maybe (Textual Double))
    , _jsNumChildJobs        :: !(Maybe (Textual Int64))
    , _jsTotalSlotMs         :: !(Maybe (Textual Int64))
    , _jsLoad                :: !(Maybe JobStatistics3)
    , _jsTotalBytesProcessed :: !(Maybe (Textual Int64))
    , _jsQuotaDeferments     :: !(Maybe [Text])
    , _jsEndTime             :: !(Maybe (Textual Int64))
    , _jsQuery               :: !(Maybe JobStatistics2)
    , _jsExtract             :: !(Maybe JobStatistics4)
    , _jsReservationUsage    :: !(Maybe [JobStatisticsReservationUsageItem])
    , _jsParentJobId         :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobStatistics
    :: JobStatistics
jobStatistics =
  JobStatistics'
    { _jsCreationTime = Nothing
    , _jsStartTime = Nothing
    , _jsCompletionRatio = Nothing
    , _jsNumChildJobs = Nothing
    , _jsTotalSlotMs = Nothing
    , _jsLoad = Nothing
    , _jsTotalBytesProcessed = Nothing
    , _jsQuotaDeferments = Nothing
    , _jsEndTime = Nothing
    , _jsQuery = Nothing
    , _jsExtract = Nothing
    , _jsReservationUsage = Nothing
    , _jsParentJobId = Nothing
    }
jsCreationTime :: Lens' JobStatistics (Maybe Int64)
jsCreationTime
  = lens _jsCreationTime
      (\ s a -> s{_jsCreationTime = a})
      . mapping _Coerce
jsStartTime :: Lens' JobStatistics (Maybe Int64)
jsStartTime
  = lens _jsStartTime (\ s a -> s{_jsStartTime = a}) .
      mapping _Coerce
jsCompletionRatio :: Lens' JobStatistics (Maybe Double)
jsCompletionRatio
  = lens _jsCompletionRatio
      (\ s a -> s{_jsCompletionRatio = a})
      . mapping _Coerce
jsNumChildJobs :: Lens' JobStatistics (Maybe Int64)
jsNumChildJobs
  = lens _jsNumChildJobs
      (\ s a -> s{_jsNumChildJobs = a})
      . mapping _Coerce
jsTotalSlotMs :: Lens' JobStatistics (Maybe Int64)
jsTotalSlotMs
  = lens _jsTotalSlotMs
      (\ s a -> s{_jsTotalSlotMs = a})
      . mapping _Coerce
jsLoad :: Lens' JobStatistics (Maybe JobStatistics3)
jsLoad = lens _jsLoad (\ s a -> s{_jsLoad = a})
jsTotalBytesProcessed :: Lens' JobStatistics (Maybe Int64)
jsTotalBytesProcessed
  = lens _jsTotalBytesProcessed
      (\ s a -> s{_jsTotalBytesProcessed = a})
      . mapping _Coerce
jsQuotaDeferments :: Lens' JobStatistics [Text]
jsQuotaDeferments
  = lens _jsQuotaDeferments
      (\ s a -> s{_jsQuotaDeferments = a})
      . _Default
      . _Coerce
jsEndTime :: Lens' JobStatistics (Maybe Int64)
jsEndTime
  = lens _jsEndTime (\ s a -> s{_jsEndTime = a}) .
      mapping _Coerce
jsQuery :: Lens' JobStatistics (Maybe JobStatistics2)
jsQuery = lens _jsQuery (\ s a -> s{_jsQuery = a})
jsExtract :: Lens' JobStatistics (Maybe JobStatistics4)
jsExtract
  = lens _jsExtract (\ s a -> s{_jsExtract = a})
jsReservationUsage :: Lens' JobStatistics [JobStatisticsReservationUsageItem]
jsReservationUsage
  = lens _jsReservationUsage
      (\ s a -> s{_jsReservationUsage = a})
      . _Default
      . _Coerce
jsParentJobId :: Lens' JobStatistics (Maybe Text)
jsParentJobId
  = lens _jsParentJobId
      (\ s a -> s{_jsParentJobId = a})
instance FromJSON JobStatistics where
        parseJSON
          = withObject "JobStatistics"
              (\ o ->
                 JobStatistics' <$>
                   (o .:? "creationTime") <*> (o .:? "startTime") <*>
                     (o .:? "completionRatio")
                     <*> (o .:? "numChildJobs")
                     <*> (o .:? "totalSlotMs")
                     <*> (o .:? "load")
                     <*> (o .:? "totalBytesProcessed")
                     <*> (o .:? "quotaDeferments" .!= mempty)
                     <*> (o .:? "endTime")
                     <*> (o .:? "query")
                     <*> (o .:? "extract")
                     <*> (o .:? "reservationUsage" .!= mempty)
                     <*> (o .:? "parentJobId"))
instance ToJSON JobStatistics where
        toJSON JobStatistics'{..}
          = object
              (catMaybes
                 [("creationTime" .=) <$> _jsCreationTime,
                  ("startTime" .=) <$> _jsStartTime,
                  ("completionRatio" .=) <$> _jsCompletionRatio,
                  ("numChildJobs" .=) <$> _jsNumChildJobs,
                  ("totalSlotMs" .=) <$> _jsTotalSlotMs,
                  ("load" .=) <$> _jsLoad,
                  ("totalBytesProcessed" .=) <$>
                    _jsTotalBytesProcessed,
                  ("quotaDeferments" .=) <$> _jsQuotaDeferments,
                  ("endTime" .=) <$> _jsEndTime,
                  ("query" .=) <$> _jsQuery,
                  ("extract" .=) <$> _jsExtract,
                  ("reservationUsage" .=) <$> _jsReservationUsage,
                  ("parentJobId" .=) <$> _jsParentJobId])
newtype JobConfigurationLabels =
  JobConfigurationLabels'
    { _jclAddtional :: HashMap Text Text
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobConfigurationLabels
    :: HashMap Text Text 
    -> JobConfigurationLabels
jobConfigurationLabels pJclAddtional_ =
  JobConfigurationLabels' {_jclAddtional = _Coerce # pJclAddtional_}
jclAddtional :: Lens' JobConfigurationLabels (HashMap Text Text)
jclAddtional
  = lens _jclAddtional (\ s a -> s{_jclAddtional = a})
      . _Coerce
instance FromJSON JobConfigurationLabels where
        parseJSON
          = withObject "JobConfigurationLabels"
              (\ o ->
                 JobConfigurationLabels' <$> (parseJSONObject o))
instance ToJSON JobConfigurationLabels where
        toJSON = toJSON . _jclAddtional
data DataSet =
  DataSet'
    { _dsCreationTime                 :: !(Maybe (Textual Int64))
    , _dsDefaultPartitionExpirationMs :: !(Maybe (Textual Int64))
    , _dsAccess                       :: !(Maybe [DataSetAccessItem])
    , _dsEtag                         :: !(Maybe Text)
    , _dsLocation                     :: !(Maybe Text)
    , _dsFriendlyName                 :: !(Maybe Text)
    , _dsKind                         :: !Text
    , _dsLastModifiedTime             :: !(Maybe (Textual Int64))
    , _dsDataSetReference             :: !(Maybe DataSetReference)
    , _dsSelfLink                     :: !(Maybe Text)
    , _dsId                           :: !(Maybe Text)
    , _dsLabels                       :: !(Maybe DataSetLabels)
    , _dsDefaultTableExpirationMs     :: !(Maybe (Textual Int64))
    , _dsDescription                  :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
dataSet
    :: DataSet
dataSet =
  DataSet'
    { _dsCreationTime = Nothing
    , _dsDefaultPartitionExpirationMs = Nothing
    , _dsAccess = Nothing
    , _dsEtag = Nothing
    , _dsLocation = Nothing
    , _dsFriendlyName = Nothing
    , _dsKind = "bigquery#dataset"
    , _dsLastModifiedTime = Nothing
    , _dsDataSetReference = Nothing
    , _dsSelfLink = Nothing
    , _dsId = Nothing
    , _dsLabels = Nothing
    , _dsDefaultTableExpirationMs = Nothing
    , _dsDescription = Nothing
    }
dsCreationTime :: Lens' DataSet (Maybe Int64)
dsCreationTime
  = lens _dsCreationTime
      (\ s a -> s{_dsCreationTime = a})
      . mapping _Coerce
dsDefaultPartitionExpirationMs :: Lens' DataSet (Maybe Int64)
dsDefaultPartitionExpirationMs
  = lens _dsDefaultPartitionExpirationMs
      (\ s a -> s{_dsDefaultPartitionExpirationMs = a})
      . mapping _Coerce
dsAccess :: Lens' DataSet [DataSetAccessItem]
dsAccess
  = lens _dsAccess (\ s a -> s{_dsAccess = a}) .
      _Default
      . _Coerce
dsEtag :: Lens' DataSet (Maybe Text)
dsEtag = lens _dsEtag (\ s a -> s{_dsEtag = a})
dsLocation :: Lens' DataSet (Maybe Text)
dsLocation
  = lens _dsLocation (\ s a -> s{_dsLocation = a})
dsFriendlyName :: Lens' DataSet (Maybe Text)
dsFriendlyName
  = lens _dsFriendlyName
      (\ s a -> s{_dsFriendlyName = a})
dsKind :: Lens' DataSet Text
dsKind = lens _dsKind (\ s a -> s{_dsKind = a})
dsLastModifiedTime :: Lens' DataSet (Maybe Int64)
dsLastModifiedTime
  = lens _dsLastModifiedTime
      (\ s a -> s{_dsLastModifiedTime = a})
      . mapping _Coerce
dsDataSetReference :: Lens' DataSet (Maybe DataSetReference)
dsDataSetReference
  = lens _dsDataSetReference
      (\ s a -> s{_dsDataSetReference = a})
dsSelfLink :: Lens' DataSet (Maybe Text)
dsSelfLink
  = lens _dsSelfLink (\ s a -> s{_dsSelfLink = a})
dsId :: Lens' DataSet (Maybe Text)
dsId = lens _dsId (\ s a -> s{_dsId = a})
dsLabels :: Lens' DataSet (Maybe DataSetLabels)
dsLabels = lens _dsLabels (\ s a -> s{_dsLabels = a})
dsDefaultTableExpirationMs :: Lens' DataSet (Maybe Int64)
dsDefaultTableExpirationMs
  = lens _dsDefaultTableExpirationMs
      (\ s a -> s{_dsDefaultTableExpirationMs = a})
      . mapping _Coerce
dsDescription :: Lens' DataSet (Maybe Text)
dsDescription
  = lens _dsDescription
      (\ s a -> s{_dsDescription = a})
instance FromJSON DataSet where
        parseJSON
          = withObject "DataSet"
              (\ o ->
                 DataSet' <$>
                   (o .:? "creationTime") <*>
                     (o .:? "defaultPartitionExpirationMs")
                     <*> (o .:? "access" .!= mempty)
                     <*> (o .:? "etag")
                     <*> (o .:? "location")
                     <*> (o .:? "friendlyName")
                     <*> (o .:? "kind" .!= "bigquery#dataset")
                     <*> (o .:? "lastModifiedTime")
                     <*> (o .:? "datasetReference")
                     <*> (o .:? "selfLink")
                     <*> (o .:? "id")
                     <*> (o .:? "labels")
                     <*> (o .:? "defaultTableExpirationMs")
                     <*> (o .:? "description"))
instance ToJSON DataSet where
        toJSON DataSet'{..}
          = object
              (catMaybes
                 [("creationTime" .=) <$> _dsCreationTime,
                  ("defaultPartitionExpirationMs" .=) <$>
                    _dsDefaultPartitionExpirationMs,
                  ("access" .=) <$> _dsAccess, ("etag" .=) <$> _dsEtag,
                  ("location" .=) <$> _dsLocation,
                  ("friendlyName" .=) <$> _dsFriendlyName,
                  Just ("kind" .= _dsKind),
                  ("lastModifiedTime" .=) <$> _dsLastModifiedTime,
                  ("datasetReference" .=) <$> _dsDataSetReference,
                  ("selfLink" .=) <$> _dsSelfLink, ("id" .=) <$> _dsId,
                  ("labels" .=) <$> _dsLabels,
                  ("defaultTableExpirationMs" .=) <$>
                    _dsDefaultTableExpirationMs,
                  ("description" .=) <$> _dsDescription])
data RangePartitioningRange =
  RangePartitioningRange'
    { _rprStart    :: !(Maybe (Textual Int64))
    , _rprInterval :: !(Maybe (Textual Int64))
    , _rprEnd      :: !(Maybe (Textual Int64))
    }
  deriving (Eq, Show, Data, Typeable, Generic)
rangePartitioningRange
    :: RangePartitioningRange
rangePartitioningRange =
  RangePartitioningRange'
    {_rprStart = Nothing, _rprInterval = Nothing, _rprEnd = Nothing}
rprStart :: Lens' RangePartitioningRange (Maybe Int64)
rprStart
  = lens _rprStart (\ s a -> s{_rprStart = a}) .
      mapping _Coerce
rprInterval :: Lens' RangePartitioningRange (Maybe Int64)
rprInterval
  = lens _rprInterval (\ s a -> s{_rprInterval = a}) .
      mapping _Coerce
rprEnd :: Lens' RangePartitioningRange (Maybe Int64)
rprEnd
  = lens _rprEnd (\ s a -> s{_rprEnd = a}) .
      mapping _Coerce
instance FromJSON RangePartitioningRange where
        parseJSON
          = withObject "RangePartitioningRange"
              (\ o ->
                 RangePartitioningRange' <$>
                   (o .:? "start") <*> (o .:? "interval") <*>
                     (o .:? "end"))
instance ToJSON RangePartitioningRange where
        toJSON RangePartitioningRange'{..}
          = object
              (catMaybes
                 [("start" .=) <$> _rprStart,
                  ("interval" .=) <$> _rprInterval,
                  ("end" .=) <$> _rprEnd])
data JobStatisticsReservationUsageItem =
  JobStatisticsReservationUsageItem'
    { _jsruiName   :: !(Maybe Text)
    , _jsruiSlotMs :: !(Maybe (Textual Int64))
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobStatisticsReservationUsageItem
    :: JobStatisticsReservationUsageItem
jobStatisticsReservationUsageItem =
  JobStatisticsReservationUsageItem'
    {_jsruiName = Nothing, _jsruiSlotMs = Nothing}
jsruiName :: Lens' JobStatisticsReservationUsageItem (Maybe Text)
jsruiName
  = lens _jsruiName (\ s a -> s{_jsruiName = a})
jsruiSlotMs :: Lens' JobStatisticsReservationUsageItem (Maybe Int64)
jsruiSlotMs
  = lens _jsruiSlotMs (\ s a -> s{_jsruiSlotMs = a}) .
      mapping _Coerce
instance FromJSON JobStatisticsReservationUsageItem
         where
        parseJSON
          = withObject "JobStatisticsReservationUsageItem"
              (\ o ->
                 JobStatisticsReservationUsageItem' <$>
                   (o .:? "name") <*> (o .:? "slotMs"))
instance ToJSON JobStatisticsReservationUsageItem
         where
        toJSON JobStatisticsReservationUsageItem'{..}
          = object
              (catMaybes
                 [("name" .=) <$> _jsruiName,
                  ("slotMs" .=) <$> _jsruiSlotMs])
data BigtableOptions =
  BigtableOptions'
    { _boReadRowkeyAsString              :: !(Maybe Bool)
    , _boIgnoreUnspecifiedColumnFamilies :: !(Maybe Bool)
    , _boColumnFamilies                  :: !(Maybe [BigtableColumnFamily])
    }
  deriving (Eq, Show, Data, Typeable, Generic)
bigtableOptions
    :: BigtableOptions
bigtableOptions =
  BigtableOptions'
    { _boReadRowkeyAsString = Nothing
    , _boIgnoreUnspecifiedColumnFamilies = Nothing
    , _boColumnFamilies = Nothing
    }
boReadRowkeyAsString :: Lens' BigtableOptions (Maybe Bool)
boReadRowkeyAsString
  = lens _boReadRowkeyAsString
      (\ s a -> s{_boReadRowkeyAsString = a})
boIgnoreUnspecifiedColumnFamilies :: Lens' BigtableOptions (Maybe Bool)
boIgnoreUnspecifiedColumnFamilies
  = lens _boIgnoreUnspecifiedColumnFamilies
      (\ s a -> s{_boIgnoreUnspecifiedColumnFamilies = a})
boColumnFamilies :: Lens' BigtableOptions [BigtableColumnFamily]
boColumnFamilies
  = lens _boColumnFamilies
      (\ s a -> s{_boColumnFamilies = a})
      . _Default
      . _Coerce
instance FromJSON BigtableOptions where
        parseJSON
          = withObject "BigtableOptions"
              (\ o ->
                 BigtableOptions' <$>
                   (o .:? "readRowkeyAsString") <*>
                     (o .:? "ignoreUnspecifiedColumnFamilies")
                     <*> (o .:? "columnFamilies" .!= mempty))
instance ToJSON BigtableOptions where
        toJSON BigtableOptions'{..}
          = object
              (catMaybes
                 [("readRowkeyAsString" .=) <$> _boReadRowkeyAsString,
                  ("ignoreUnspecifiedColumnFamilies" .=) <$>
                    _boIgnoreUnspecifiedColumnFamilies,
                  ("columnFamilies" .=) <$> _boColumnFamilies])
newtype Clustering =
  Clustering'
    { _cFields :: Maybe [Text]
    }
  deriving (Eq, Show, Data, Typeable, Generic)
clustering
    :: Clustering
clustering = Clustering' {_cFields = Nothing}
cFields :: Lens' Clustering [Text]
cFields
  = lens _cFields (\ s a -> s{_cFields = a}) . _Default
      . _Coerce
instance FromJSON Clustering where
        parseJSON
          = withObject "Clustering"
              (\ o -> Clustering' <$> (o .:? "fields" .!= mempty))
instance ToJSON Clustering where
        toJSON Clustering'{..}
          = object (catMaybes [("fields" .=) <$> _cFields])
data ExternalDataConfiguration =
  ExternalDataConfiguration'
    { _edcBigtableOptions      :: !(Maybe BigtableOptions)
    , _edcIgnoreUnknownValues  :: !(Maybe Bool)
    , _edcHivePartitioningMode :: !(Maybe Text)
    , _edcCompression          :: !(Maybe Text)
    , _edcSourceFormat         :: !(Maybe Text)
    , _edcSchema               :: !(Maybe TableSchema)
    , _edcMaxBadRecords        :: !(Maybe (Textual Int32))
    , _edcGoogleSheetsOptions  :: !(Maybe GoogleSheetsOptions)
    , _edcAutodetect           :: !(Maybe Bool)
    , _edcSourceURIs           :: !(Maybe [Text])
    , _edcCSVOptions           :: !(Maybe CSVOptions)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
externalDataConfiguration
    :: ExternalDataConfiguration
externalDataConfiguration =
  ExternalDataConfiguration'
    { _edcBigtableOptions = Nothing
    , _edcIgnoreUnknownValues = Nothing
    , _edcHivePartitioningMode = Nothing
    , _edcCompression = Nothing
    , _edcSourceFormat = Nothing
    , _edcSchema = Nothing
    , _edcMaxBadRecords = Nothing
    , _edcGoogleSheetsOptions = Nothing
    , _edcAutodetect = Nothing
    , _edcSourceURIs = Nothing
    , _edcCSVOptions = Nothing
    }
edcBigtableOptions :: Lens' ExternalDataConfiguration (Maybe BigtableOptions)
edcBigtableOptions
  = lens _edcBigtableOptions
      (\ s a -> s{_edcBigtableOptions = a})
edcIgnoreUnknownValues :: Lens' ExternalDataConfiguration (Maybe Bool)
edcIgnoreUnknownValues
  = lens _edcIgnoreUnknownValues
      (\ s a -> s{_edcIgnoreUnknownValues = a})
edcHivePartitioningMode :: Lens' ExternalDataConfiguration (Maybe Text)
edcHivePartitioningMode
  = lens _edcHivePartitioningMode
      (\ s a -> s{_edcHivePartitioningMode = a})
edcCompression :: Lens' ExternalDataConfiguration (Maybe Text)
edcCompression
  = lens _edcCompression
      (\ s a -> s{_edcCompression = a})
edcSourceFormat :: Lens' ExternalDataConfiguration (Maybe Text)
edcSourceFormat
  = lens _edcSourceFormat
      (\ s a -> s{_edcSourceFormat = a})
edcSchema :: Lens' ExternalDataConfiguration (Maybe TableSchema)
edcSchema
  = lens _edcSchema (\ s a -> s{_edcSchema = a})
edcMaxBadRecords :: Lens' ExternalDataConfiguration (Maybe Int32)
edcMaxBadRecords
  = lens _edcMaxBadRecords
      (\ s a -> s{_edcMaxBadRecords = a})
      . mapping _Coerce
edcGoogleSheetsOptions :: Lens' ExternalDataConfiguration (Maybe GoogleSheetsOptions)
edcGoogleSheetsOptions
  = lens _edcGoogleSheetsOptions
      (\ s a -> s{_edcGoogleSheetsOptions = a})
edcAutodetect :: Lens' ExternalDataConfiguration (Maybe Bool)
edcAutodetect
  = lens _edcAutodetect
      (\ s a -> s{_edcAutodetect = a})
edcSourceURIs :: Lens' ExternalDataConfiguration [Text]
edcSourceURIs
  = lens _edcSourceURIs
      (\ s a -> s{_edcSourceURIs = a})
      . _Default
      . _Coerce
edcCSVOptions :: Lens' ExternalDataConfiguration (Maybe CSVOptions)
edcCSVOptions
  = lens _edcCSVOptions
      (\ s a -> s{_edcCSVOptions = a})
instance FromJSON ExternalDataConfiguration where
        parseJSON
          = withObject "ExternalDataConfiguration"
              (\ o ->
                 ExternalDataConfiguration' <$>
                   (o .:? "bigtableOptions") <*>
                     (o .:? "ignoreUnknownValues")
                     <*> (o .:? "hivePartitioningMode")
                     <*> (o .:? "compression")
                     <*> (o .:? "sourceFormat")
                     <*> (o .:? "schema")
                     <*> (o .:? "maxBadRecords")
                     <*> (o .:? "googleSheetsOptions")
                     <*> (o .:? "autodetect")
                     <*> (o .:? "sourceUris" .!= mempty)
                     <*> (o .:? "csvOptions"))
instance ToJSON ExternalDataConfiguration where
        toJSON ExternalDataConfiguration'{..}
          = object
              (catMaybes
                 [("bigtableOptions" .=) <$> _edcBigtableOptions,
                  ("ignoreUnknownValues" .=) <$>
                    _edcIgnoreUnknownValues,
                  ("hivePartitioningMode" .=) <$>
                    _edcHivePartitioningMode,
                  ("compression" .=) <$> _edcCompression,
                  ("sourceFormat" .=) <$> _edcSourceFormat,
                  ("schema" .=) <$> _edcSchema,
                  ("maxBadRecords" .=) <$> _edcMaxBadRecords,
                  ("googleSheetsOptions" .=) <$>
                    _edcGoogleSheetsOptions,
                  ("autodetect" .=) <$> _edcAutodetect,
                  ("sourceUris" .=) <$> _edcSourceURIs,
                  ("csvOptions" .=) <$> _edcCSVOptions])
data TableReference =
  TableReference'
    { _trDataSetId :: !(Maybe Text)
    , _trProjectId :: !(Maybe Text)
    , _trTableId   :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
tableReference
    :: TableReference
tableReference =
  TableReference'
    {_trDataSetId = Nothing, _trProjectId = Nothing, _trTableId = Nothing}
trDataSetId :: Lens' TableReference (Maybe Text)
trDataSetId
  = lens _trDataSetId (\ s a -> s{_trDataSetId = a})
trProjectId :: Lens' TableReference (Maybe Text)
trProjectId
  = lens _trProjectId (\ s a -> s{_trProjectId = a})
trTableId :: Lens' TableReference (Maybe Text)
trTableId
  = lens _trTableId (\ s a -> s{_trTableId = a})
instance FromJSON TableReference where
        parseJSON
          = withObject "TableReference"
              (\ o ->
                 TableReference' <$>
                   (o .:? "datasetId") <*> (o .:? "projectId") <*>
                     (o .:? "tableId"))
instance ToJSON TableReference where
        toJSON TableReference'{..}
          = object
              (catMaybes
                 [("datasetId" .=) <$> _trDataSetId,
                  ("projectId" .=) <$> _trProjectId,
                  ("tableId" .=) <$> _trTableId])
data ModelDefinitionModelOptions =
  ModelDefinitionModelOptions'
    { _mdmoModelType :: !(Maybe Text)
    , _mdmoLabels    :: !(Maybe [Text])
    , _mdmoLossType  :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
modelDefinitionModelOptions
    :: ModelDefinitionModelOptions
modelDefinitionModelOptions =
  ModelDefinitionModelOptions'
    {_mdmoModelType = Nothing, _mdmoLabels = Nothing, _mdmoLossType = Nothing}
mdmoModelType :: Lens' ModelDefinitionModelOptions (Maybe Text)
mdmoModelType
  = lens _mdmoModelType
      (\ s a -> s{_mdmoModelType = a})
mdmoLabels :: Lens' ModelDefinitionModelOptions [Text]
mdmoLabels
  = lens _mdmoLabels (\ s a -> s{_mdmoLabels = a}) .
      _Default
      . _Coerce
mdmoLossType :: Lens' ModelDefinitionModelOptions (Maybe Text)
mdmoLossType
  = lens _mdmoLossType (\ s a -> s{_mdmoLossType = a})
instance FromJSON ModelDefinitionModelOptions where
        parseJSON
          = withObject "ModelDefinitionModelOptions"
              (\ o ->
                 ModelDefinitionModelOptions' <$>
                   (o .:? "modelType") <*> (o .:? "labels" .!= mempty)
                     <*> (o .:? "lossType"))
instance ToJSON ModelDefinitionModelOptions where
        toJSON ModelDefinitionModelOptions'{..}
          = object
              (catMaybes
                 [("modelType" .=) <$> _mdmoModelType,
                  ("labels" .=) <$> _mdmoLabels,
                  ("lossType" .=) <$> _mdmoLossType])
data RoutineReference =
  RoutineReference'
    { _rrDataSetId :: !(Maybe Text)
    , _rrProjectId :: !(Maybe Text)
    , _rrRoutineId :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
routineReference
    :: RoutineReference
routineReference =
  RoutineReference'
    {_rrDataSetId = Nothing, _rrProjectId = Nothing, _rrRoutineId = Nothing}
rrDataSetId :: Lens' RoutineReference (Maybe Text)
rrDataSetId
  = lens _rrDataSetId (\ s a -> s{_rrDataSetId = a})
rrProjectId :: Lens' RoutineReference (Maybe Text)
rrProjectId
  = lens _rrProjectId (\ s a -> s{_rrProjectId = a})
rrRoutineId :: Lens' RoutineReference (Maybe Text)
rrRoutineId
  = lens _rrRoutineId (\ s a -> s{_rrRoutineId = a})
instance FromJSON RoutineReference where
        parseJSON
          = withObject "RoutineReference"
              (\ o ->
                 RoutineReference' <$>
                   (o .:? "datasetId") <*> (o .:? "projectId") <*>
                     (o .:? "routineId"))
instance ToJSON RoutineReference where
        toJSON RoutineReference'{..}
          = object
              (catMaybes
                 [("datasetId" .=) <$> _rrDataSetId,
                  ("projectId" .=) <$> _rrProjectId,
                  ("routineId" .=) <$> _rrRoutineId])
data RangePartitioning =
  RangePartitioning'
    { _rpField :: !(Maybe Text)
    , _rpRange :: !(Maybe RangePartitioningRange)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
rangePartitioning
    :: RangePartitioning
rangePartitioning = RangePartitioning' {_rpField = Nothing, _rpRange = Nothing}
rpField :: Lens' RangePartitioning (Maybe Text)
rpField = lens _rpField (\ s a -> s{_rpField = a})
rpRange :: Lens' RangePartitioning (Maybe RangePartitioningRange)
rpRange = lens _rpRange (\ s a -> s{_rpRange = a})
instance FromJSON RangePartitioning where
        parseJSON
          = withObject "RangePartitioning"
              (\ o ->
                 RangePartitioning' <$>
                   (o .:? "field") <*> (o .:? "range"))
instance ToJSON RangePartitioning where
        toJSON RangePartitioning'{..}
          = object
              (catMaybes
                 [("field" .=) <$> _rpField,
                  ("range" .=) <$> _rpRange])
data TableFieldSchema =
  TableFieldSchema'
    { _tfsMode        :: !(Maybe Text)
    , _tfsCategories  :: !(Maybe TableFieldSchemaCategories)
    , _tfsName        :: !(Maybe Text)
    , _tfsType        :: !(Maybe Text)
    , _tfsDescription :: !(Maybe Text)
    , _tfsFields      :: !(Maybe [TableFieldSchema])
    }
  deriving (Eq, Show, Data, Typeable, Generic)
tableFieldSchema
    :: TableFieldSchema
tableFieldSchema =
  TableFieldSchema'
    { _tfsMode = Nothing
    , _tfsCategories = Nothing
    , _tfsName = Nothing
    , _tfsType = Nothing
    , _tfsDescription = Nothing
    , _tfsFields = Nothing
    }
tfsMode :: Lens' TableFieldSchema (Maybe Text)
tfsMode = lens _tfsMode (\ s a -> s{_tfsMode = a})
tfsCategories :: Lens' TableFieldSchema (Maybe TableFieldSchemaCategories)
tfsCategories
  = lens _tfsCategories
      (\ s a -> s{_tfsCategories = a})
tfsName :: Lens' TableFieldSchema (Maybe Text)
tfsName = lens _tfsName (\ s a -> s{_tfsName = a})
tfsType :: Lens' TableFieldSchema (Maybe Text)
tfsType = lens _tfsType (\ s a -> s{_tfsType = a})
tfsDescription :: Lens' TableFieldSchema (Maybe Text)
tfsDescription
  = lens _tfsDescription
      (\ s a -> s{_tfsDescription = a})
tfsFields :: Lens' TableFieldSchema [TableFieldSchema]
tfsFields
  = lens _tfsFields (\ s a -> s{_tfsFields = a}) .
      _Default
      . _Coerce
instance FromJSON TableFieldSchema where
        parseJSON
          = withObject "TableFieldSchema"
              (\ o ->
                 TableFieldSchema' <$>
                   (o .:? "mode") <*> (o .:? "categories") <*>
                     (o .:? "name")
                     <*> (o .:? "type")
                     <*> (o .:? "description")
                     <*> (o .:? "fields" .!= mempty))
instance ToJSON TableFieldSchema where
        toJSON TableFieldSchema'{..}
          = object
              (catMaybes
                 [("mode" .=) <$> _tfsMode,
                  ("categories" .=) <$> _tfsCategories,
                  ("name" .=) <$> _tfsName, ("type" .=) <$> _tfsType,
                  ("description" .=) <$> _tfsDescription,
                  ("fields" .=) <$> _tfsFields])
data GetQueryResultsResponse =
  GetQueryResultsResponse'
    { _gqrrJobReference        :: !(Maybe JobReference)
    , _gqrrEtag                :: !(Maybe Text)
    , _gqrrKind                :: !Text
    , _gqrrSchema              :: !(Maybe TableSchema)
    , _gqrrTotalBytesProcessed :: !(Maybe (Textual Int64))
    , _gqrrRows                :: !(Maybe [TableRow])
    , _gqrrPageToken           :: !(Maybe Text)
    , _gqrrNumDmlAffectedRows  :: !(Maybe (Textual Int64))
    , _gqrrTotalRows           :: !(Maybe (Textual Word64))
    , _gqrrErrors              :: !(Maybe [ErrorProto])
    , _gqrrJobComplete         :: !(Maybe Bool)
    , _gqrrCacheHit            :: !(Maybe Bool)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
getQueryResultsResponse
    :: GetQueryResultsResponse
getQueryResultsResponse =
  GetQueryResultsResponse'
    { _gqrrJobReference = Nothing
    , _gqrrEtag = Nothing
    , _gqrrKind = "bigquery#getQueryResultsResponse"
    , _gqrrSchema = Nothing
    , _gqrrTotalBytesProcessed = Nothing
    , _gqrrRows = Nothing
    , _gqrrPageToken = Nothing
    , _gqrrNumDmlAffectedRows = Nothing
    , _gqrrTotalRows = Nothing
    , _gqrrErrors = Nothing
    , _gqrrJobComplete = Nothing
    , _gqrrCacheHit = Nothing
    }
gqrrJobReference :: Lens' GetQueryResultsResponse (Maybe JobReference)
gqrrJobReference
  = lens _gqrrJobReference
      (\ s a -> s{_gqrrJobReference = a})
gqrrEtag :: Lens' GetQueryResultsResponse (Maybe Text)
gqrrEtag = lens _gqrrEtag (\ s a -> s{_gqrrEtag = a})
gqrrKind :: Lens' GetQueryResultsResponse Text
gqrrKind = lens _gqrrKind (\ s a -> s{_gqrrKind = a})
gqrrSchema :: Lens' GetQueryResultsResponse (Maybe TableSchema)
gqrrSchema
  = lens _gqrrSchema (\ s a -> s{_gqrrSchema = a})
gqrrTotalBytesProcessed :: Lens' GetQueryResultsResponse (Maybe Int64)
gqrrTotalBytesProcessed
  = lens _gqrrTotalBytesProcessed
      (\ s a -> s{_gqrrTotalBytesProcessed = a})
      . mapping _Coerce
gqrrRows :: Lens' GetQueryResultsResponse [TableRow]
gqrrRows
  = lens _gqrrRows (\ s a -> s{_gqrrRows = a}) .
      _Default
      . _Coerce
gqrrPageToken :: Lens' GetQueryResultsResponse (Maybe Text)
gqrrPageToken
  = lens _gqrrPageToken
      (\ s a -> s{_gqrrPageToken = a})
gqrrNumDmlAffectedRows :: Lens' GetQueryResultsResponse (Maybe Int64)
gqrrNumDmlAffectedRows
  = lens _gqrrNumDmlAffectedRows
      (\ s a -> s{_gqrrNumDmlAffectedRows = a})
      . mapping _Coerce
gqrrTotalRows :: Lens' GetQueryResultsResponse (Maybe Word64)
gqrrTotalRows
  = lens _gqrrTotalRows
      (\ s a -> s{_gqrrTotalRows = a})
      . mapping _Coerce
gqrrErrors :: Lens' GetQueryResultsResponse [ErrorProto]
gqrrErrors
  = lens _gqrrErrors (\ s a -> s{_gqrrErrors = a}) .
      _Default
      . _Coerce
gqrrJobComplete :: Lens' GetQueryResultsResponse (Maybe Bool)
gqrrJobComplete
  = lens _gqrrJobComplete
      (\ s a -> s{_gqrrJobComplete = a})
gqrrCacheHit :: Lens' GetQueryResultsResponse (Maybe Bool)
gqrrCacheHit
  = lens _gqrrCacheHit (\ s a -> s{_gqrrCacheHit = a})
instance FromJSON GetQueryResultsResponse where
        parseJSON
          = withObject "GetQueryResultsResponse"
              (\ o ->
                 GetQueryResultsResponse' <$>
                   (o .:? "jobReference") <*> (o .:? "etag") <*>
                     (o .:? "kind" .!= "bigquery#getQueryResultsResponse")
                     <*> (o .:? "schema")
                     <*> (o .:? "totalBytesProcessed")
                     <*> (o .:? "rows" .!= mempty)
                     <*> (o .:? "pageToken")
                     <*> (o .:? "numDmlAffectedRows")
                     <*> (o .:? "totalRows")
                     <*> (o .:? "errors" .!= mempty)
                     <*> (o .:? "jobComplete")
                     <*> (o .:? "cacheHit"))
instance ToJSON GetQueryResultsResponse where
        toJSON GetQueryResultsResponse'{..}
          = object
              (catMaybes
                 [("jobReference" .=) <$> _gqrrJobReference,
                  ("etag" .=) <$> _gqrrEtag,
                  Just ("kind" .= _gqrrKind),
                  ("schema" .=) <$> _gqrrSchema,
                  ("totalBytesProcessed" .=) <$>
                    _gqrrTotalBytesProcessed,
                  ("rows" .=) <$> _gqrrRows,
                  ("pageToken" .=) <$> _gqrrPageToken,
                  ("numDmlAffectedRows" .=) <$>
                    _gqrrNumDmlAffectedRows,
                  ("totalRows" .=) <$> _gqrrTotalRows,
                  ("errors" .=) <$> _gqrrErrors,
                  ("jobComplete" .=) <$> _gqrrJobComplete,
                  ("cacheHit" .=) <$> _gqrrCacheHit])
data DataSetList =
  DataSetList'
    { _dslEtag          :: !(Maybe Text)
    , _dslNextPageToken :: !(Maybe Text)
    , _dslKind          :: !Text
    , _dslDataSets      :: !(Maybe [DataSetListDataSetsItem])
    }
  deriving (Eq, Show, Data, Typeable, Generic)
dataSetList
    :: DataSetList
dataSetList =
  DataSetList'
    { _dslEtag = Nothing
    , _dslNextPageToken = Nothing
    , _dslKind = "bigquery#datasetList"
    , _dslDataSets = Nothing
    }
dslEtag :: Lens' DataSetList (Maybe Text)
dslEtag = lens _dslEtag (\ s a -> s{_dslEtag = a})
dslNextPageToken :: Lens' DataSetList (Maybe Text)
dslNextPageToken
  = lens _dslNextPageToken
      (\ s a -> s{_dslNextPageToken = a})
dslKind :: Lens' DataSetList Text
dslKind = lens _dslKind (\ s a -> s{_dslKind = a})
dslDataSets :: Lens' DataSetList [DataSetListDataSetsItem]
dslDataSets
  = lens _dslDataSets (\ s a -> s{_dslDataSets = a}) .
      _Default
      . _Coerce
instance FromJSON DataSetList where
        parseJSON
          = withObject "DataSetList"
              (\ o ->
                 DataSetList' <$>
                   (o .:? "etag") <*> (o .:? "nextPageToken") <*>
                     (o .:? "kind" .!= "bigquery#datasetList")
                     <*> (o .:? "datasets" .!= mempty))
instance ToJSON DataSetList where
        toJSON DataSetList'{..}
          = object
              (catMaybes
                 [("etag" .=) <$> _dslEtag,
                  ("nextPageToken" .=) <$> _dslNextPageToken,
                  Just ("kind" .= _dslKind),
                  ("datasets" .=) <$> _dslDataSets])
data QueryRequest =
  QueryRequest'
    { _qrLocation        :: !(Maybe Text)
    , _qrUseQueryCache   :: !Bool
    , _qrPreserveNulls   :: !(Maybe Bool)
    , _qrKind            :: !Text
    , _qrQueryParameters :: !(Maybe [QueryParameter])
    , _qrQuery           :: !(Maybe Text)
    , _qrParameterMode   :: !(Maybe Text)
    , _qrTimeoutMs       :: !(Maybe (Textual Word32))
    , _qrUseLegacySQL    :: !Bool
    , _qrDryRun          :: !(Maybe Bool)
    , _qrMaxResults      :: !(Maybe (Textual Word32))
    , _qrDefaultDataSet  :: !(Maybe DataSetReference)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
queryRequest
    :: QueryRequest
queryRequest =
  QueryRequest'
    { _qrLocation = Nothing
    , _qrUseQueryCache = True
    , _qrPreserveNulls = Nothing
    , _qrKind = "bigquery#queryRequest"
    , _qrQueryParameters = Nothing
    , _qrQuery = Nothing
    , _qrParameterMode = Nothing
    , _qrTimeoutMs = Nothing
    , _qrUseLegacySQL = True
    , _qrDryRun = Nothing
    , _qrMaxResults = Nothing
    , _qrDefaultDataSet = Nothing
    }
qrLocation :: Lens' QueryRequest (Maybe Text)
qrLocation
  = lens _qrLocation (\ s a -> s{_qrLocation = a})
qrUseQueryCache :: Lens' QueryRequest Bool
qrUseQueryCache
  = lens _qrUseQueryCache
      (\ s a -> s{_qrUseQueryCache = a})
qrPreserveNulls :: Lens' QueryRequest (Maybe Bool)
qrPreserveNulls
  = lens _qrPreserveNulls
      (\ s a -> s{_qrPreserveNulls = a})
qrKind :: Lens' QueryRequest Text
qrKind = lens _qrKind (\ s a -> s{_qrKind = a})
qrQueryParameters :: Lens' QueryRequest [QueryParameter]
qrQueryParameters
  = lens _qrQueryParameters
      (\ s a -> s{_qrQueryParameters = a})
      . _Default
      . _Coerce
qrQuery :: Lens' QueryRequest (Maybe Text)
qrQuery = lens _qrQuery (\ s a -> s{_qrQuery = a})
qrParameterMode :: Lens' QueryRequest (Maybe Text)
qrParameterMode
  = lens _qrParameterMode
      (\ s a -> s{_qrParameterMode = a})
qrTimeoutMs :: Lens' QueryRequest (Maybe Word32)
qrTimeoutMs
  = lens _qrTimeoutMs (\ s a -> s{_qrTimeoutMs = a}) .
      mapping _Coerce
qrUseLegacySQL :: Lens' QueryRequest Bool
qrUseLegacySQL
  = lens _qrUseLegacySQL
      (\ s a -> s{_qrUseLegacySQL = a})
qrDryRun :: Lens' QueryRequest (Maybe Bool)
qrDryRun = lens _qrDryRun (\ s a -> s{_qrDryRun = a})
qrMaxResults :: Lens' QueryRequest (Maybe Word32)
qrMaxResults
  = lens _qrMaxResults (\ s a -> s{_qrMaxResults = a})
      . mapping _Coerce
qrDefaultDataSet :: Lens' QueryRequest (Maybe DataSetReference)
qrDefaultDataSet
  = lens _qrDefaultDataSet
      (\ s a -> s{_qrDefaultDataSet = a})
instance FromJSON QueryRequest where
        parseJSON
          = withObject "QueryRequest"
              (\ o ->
                 QueryRequest' <$>
                   (o .:? "location") <*>
                     (o .:? "useQueryCache" .!= True)
                     <*> (o .:? "preserveNulls")
                     <*> (o .:? "kind" .!= "bigquery#queryRequest")
                     <*> (o .:? "queryParameters" .!= mempty)
                     <*> (o .:? "query")
                     <*> (o .:? "parameterMode")
                     <*> (o .:? "timeoutMs")
                     <*> (o .:? "useLegacySql" .!= True)
                     <*> (o .:? "dryRun")
                     <*> (o .:? "maxResults")
                     <*> (o .:? "defaultDataset"))
instance ToJSON QueryRequest where
        toJSON QueryRequest'{..}
          = object
              (catMaybes
                 [("location" .=) <$> _qrLocation,
                  Just ("useQueryCache" .= _qrUseQueryCache),
                  ("preserveNulls" .=) <$> _qrPreserveNulls,
                  Just ("kind" .= _qrKind),
                  ("queryParameters" .=) <$> _qrQueryParameters,
                  ("query" .=) <$> _qrQuery,
                  ("parameterMode" .=) <$> _qrParameterMode,
                  ("timeoutMs" .=) <$> _qrTimeoutMs,
                  Just ("useLegacySql" .= _qrUseLegacySQL),
                  ("dryRun" .=) <$> _qrDryRun,
                  ("maxResults" .=) <$> _qrMaxResults,
                  ("defaultDataset" .=) <$> _qrDefaultDataSet])
data BqmlTrainingRunTrainingOptions =
  BqmlTrainingRunTrainingOptions'
    { _btrtoLineSearchInitLearnRate :: !(Maybe (Textual Double))
    , _btrtoMinRelProgress          :: !(Maybe (Textual Double))
    , _btrtoL1Reg                   :: !(Maybe (Textual Double))
    , _btrtoLearnRate               :: !(Maybe (Textual Double))
    , _btrtoLearnRateStrategy       :: !(Maybe Text)
    , _btrtoMaxIteration            :: !(Maybe (Textual Int64))
    , _btrtoEarlyStop               :: !(Maybe Bool)
    , _btrtoL2Reg                   :: !(Maybe (Textual Double))
    , _btrtoWarmStart               :: !(Maybe Bool)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
bqmlTrainingRunTrainingOptions
    :: BqmlTrainingRunTrainingOptions
bqmlTrainingRunTrainingOptions =
  BqmlTrainingRunTrainingOptions'
    { _btrtoLineSearchInitLearnRate = Nothing
    , _btrtoMinRelProgress = Nothing
    , _btrtoL1Reg = Nothing
    , _btrtoLearnRate = Nothing
    , _btrtoLearnRateStrategy = Nothing
    , _btrtoMaxIteration = Nothing
    , _btrtoEarlyStop = Nothing
    , _btrtoL2Reg = Nothing
    , _btrtoWarmStart = Nothing
    }
btrtoLineSearchInitLearnRate :: Lens' BqmlTrainingRunTrainingOptions (Maybe Double)
btrtoLineSearchInitLearnRate
  = lens _btrtoLineSearchInitLearnRate
      (\ s a -> s{_btrtoLineSearchInitLearnRate = a})
      . mapping _Coerce
btrtoMinRelProgress :: Lens' BqmlTrainingRunTrainingOptions (Maybe Double)
btrtoMinRelProgress
  = lens _btrtoMinRelProgress
      (\ s a -> s{_btrtoMinRelProgress = a})
      . mapping _Coerce
btrtoL1Reg :: Lens' BqmlTrainingRunTrainingOptions (Maybe Double)
btrtoL1Reg
  = lens _btrtoL1Reg (\ s a -> s{_btrtoL1Reg = a}) .
      mapping _Coerce
btrtoLearnRate :: Lens' BqmlTrainingRunTrainingOptions (Maybe Double)
btrtoLearnRate
  = lens _btrtoLearnRate
      (\ s a -> s{_btrtoLearnRate = a})
      . mapping _Coerce
btrtoLearnRateStrategy :: Lens' BqmlTrainingRunTrainingOptions (Maybe Text)
btrtoLearnRateStrategy
  = lens _btrtoLearnRateStrategy
      (\ s a -> s{_btrtoLearnRateStrategy = a})
btrtoMaxIteration :: Lens' BqmlTrainingRunTrainingOptions (Maybe Int64)
btrtoMaxIteration
  = lens _btrtoMaxIteration
      (\ s a -> s{_btrtoMaxIteration = a})
      . mapping _Coerce
btrtoEarlyStop :: Lens' BqmlTrainingRunTrainingOptions (Maybe Bool)
btrtoEarlyStop
  = lens _btrtoEarlyStop
      (\ s a -> s{_btrtoEarlyStop = a})
btrtoL2Reg :: Lens' BqmlTrainingRunTrainingOptions (Maybe Double)
btrtoL2Reg
  = lens _btrtoL2Reg (\ s a -> s{_btrtoL2Reg = a}) .
      mapping _Coerce
btrtoWarmStart :: Lens' BqmlTrainingRunTrainingOptions (Maybe Bool)
btrtoWarmStart
  = lens _btrtoWarmStart
      (\ s a -> s{_btrtoWarmStart = a})
instance FromJSON BqmlTrainingRunTrainingOptions
         where
        parseJSON
          = withObject "BqmlTrainingRunTrainingOptions"
              (\ o ->
                 BqmlTrainingRunTrainingOptions' <$>
                   (o .:? "lineSearchInitLearnRate") <*>
                     (o .:? "minRelProgress")
                     <*> (o .:? "l1Reg")
                     <*> (o .:? "learnRate")
                     <*> (o .:? "learnRateStrategy")
                     <*> (o .:? "maxIteration")
                     <*> (o .:? "earlyStop")
                     <*> (o .:? "l2Reg")
                     <*> (o .:? "warmStart"))
instance ToJSON BqmlTrainingRunTrainingOptions where
        toJSON BqmlTrainingRunTrainingOptions'{..}
          = object
              (catMaybes
                 [("lineSearchInitLearnRate" .=) <$>
                    _btrtoLineSearchInitLearnRate,
                  ("minRelProgress" .=) <$> _btrtoMinRelProgress,
                  ("l1Reg" .=) <$> _btrtoL1Reg,
                  ("learnRate" .=) <$> _btrtoLearnRate,
                  ("learnRateStrategy" .=) <$> _btrtoLearnRateStrategy,
                  ("maxIteration" .=) <$> _btrtoMaxIteration,
                  ("earlyStop" .=) <$> _btrtoEarlyStop,
                  ("l2Reg" .=) <$> _btrtoL2Reg,
                  ("warmStart" .=) <$> _btrtoWarmStart])
data QueryParameter =
  QueryParameter'
    { _qpParameterValue :: !(Maybe QueryParameterValue)
    , _qpParameterType  :: !(Maybe QueryParameterType)
    , _qpName           :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
queryParameter
    :: QueryParameter
queryParameter =
  QueryParameter'
    {_qpParameterValue = Nothing, _qpParameterType = Nothing, _qpName = Nothing}
qpParameterValue :: Lens' QueryParameter (Maybe QueryParameterValue)
qpParameterValue
  = lens _qpParameterValue
      (\ s a -> s{_qpParameterValue = a})
qpParameterType :: Lens' QueryParameter (Maybe QueryParameterType)
qpParameterType
  = lens _qpParameterType
      (\ s a -> s{_qpParameterType = a})
qpName :: Lens' QueryParameter (Maybe Text)
qpName = lens _qpName (\ s a -> s{_qpName = a})
instance FromJSON QueryParameter where
        parseJSON
          = withObject "QueryParameter"
              (\ o ->
                 QueryParameter' <$>
                   (o .:? "parameterValue") <*> (o .:? "parameterType")
                     <*> (o .:? "name"))
instance ToJSON QueryParameter where
        toJSON QueryParameter'{..}
          = object
              (catMaybes
                 [("parameterValue" .=) <$> _qpParameterValue,
                  ("parameterType" .=) <$> _qpParameterType,
                  ("name" .=) <$> _qpName])
data JobStatistics4 =
  JobStatistics4'
    { _jsInputBytes               :: !(Maybe (Textual Int64))
    , _jsDestinationURIFileCounts :: !(Maybe [Textual Int64])
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobStatistics4
    :: JobStatistics4
jobStatistics4 =
  JobStatistics4'
    {_jsInputBytes = Nothing, _jsDestinationURIFileCounts = Nothing}
jsInputBytes :: Lens' JobStatistics4 (Maybe Int64)
jsInputBytes
  = lens _jsInputBytes (\ s a -> s{_jsInputBytes = a})
      . mapping _Coerce
jsDestinationURIFileCounts :: Lens' JobStatistics4 [Int64]
jsDestinationURIFileCounts
  = lens _jsDestinationURIFileCounts
      (\ s a -> s{_jsDestinationURIFileCounts = a})
      . _Default
      . _Coerce
instance FromJSON JobStatistics4 where
        parseJSON
          = withObject "JobStatistics4"
              (\ o ->
                 JobStatistics4' <$>
                   (o .:? "inputBytes") <*>
                     (o .:? "destinationUriFileCounts" .!= mempty))
instance ToJSON JobStatistics4 where
        toJSON JobStatistics4'{..}
          = object
              (catMaybes
                 [("inputBytes" .=) <$> _jsInputBytes,
                  ("destinationUriFileCounts" .=) <$>
                    _jsDestinationURIFileCounts])
newtype ProjectReference =
  ProjectReference'
    { _prProjectId :: Maybe Text
    }
  deriving (Eq, Show, Data, Typeable, Generic)
projectReference
    :: ProjectReference
projectReference = ProjectReference' {_prProjectId = Nothing}
prProjectId :: Lens' ProjectReference (Maybe Text)
prProjectId
  = lens _prProjectId (\ s a -> s{_prProjectId = a})
instance FromJSON ProjectReference where
        parseJSON
          = withObject "ProjectReference"
              (\ o -> ProjectReference' <$> (o .:? "projectId"))
instance ToJSON ProjectReference where
        toJSON ProjectReference'{..}
          = object
              (catMaybes [("projectId" .=) <$> _prProjectId])
data ExplainQueryStage =
  ExplainQueryStage'
    { _eqsReadMsAvg                 :: !(Maybe (Textual Int64))
    , _eqsStatus                    :: !(Maybe Text)
    , _eqsShuffleOutputBytesSpilled :: !(Maybe (Textual Int64))
    , _eqsReadMsMax                 :: !(Maybe (Textual Int64))
    , _eqsCompletedParallelInputs   :: !(Maybe (Textual Int64))
    , _eqsWaitRatioMax              :: !(Maybe (Textual Double))
    , _eqsParallelInputs            :: !(Maybe (Textual Int64))
    , _eqsShuffleOutputBytes        :: !(Maybe (Textual Int64))
    , _eqsRecordsWritten            :: !(Maybe (Textual Int64))
    , _eqsSteps                     :: !(Maybe [ExplainQueryStep])
    , _eqsInputStages               :: !(Maybe [Textual Int64])
    , _eqsWriteRatioAvg             :: !(Maybe (Textual Double))
    , _eqsRecordsRead               :: !(Maybe (Textual Int64))
    , _eqsComputeRatioAvg           :: !(Maybe (Textual Double))
    , _eqsName                      :: !(Maybe Text)
    , _eqsComputeMsMax              :: !(Maybe (Textual Int64))
    , _eqsReadRatioMax              :: !(Maybe (Textual Double))
    , _eqsWriteMsMax                :: !(Maybe (Textual Int64))
    , _eqsWaitRatioAvg              :: !(Maybe (Textual Double))
    , _eqsWaitMsAvg                 :: !(Maybe (Textual Int64))
    , _eqsId                        :: !(Maybe (Textual Int64))
    , _eqsComputeRatioMax           :: !(Maybe (Textual Double))
    , _eqsWriteRatioMax             :: !(Maybe (Textual Double))
    , _eqsComputeMsAvg              :: !(Maybe (Textual Int64))
    , _eqsReadRatioAvg              :: !(Maybe (Textual Double))
    , _eqsWriteMsAvg                :: !(Maybe (Textual Int64))
    , _eqsStartMs                   :: !(Maybe (Textual Int64))
    , _eqsEndMs                     :: !(Maybe (Textual Int64))
    , _eqsWaitMsMax                 :: !(Maybe (Textual Int64))
    }
  deriving (Eq, Show, Data, Typeable, Generic)
explainQueryStage
    :: ExplainQueryStage
explainQueryStage =
  ExplainQueryStage'
    { _eqsReadMsAvg = Nothing
    , _eqsStatus = Nothing
    , _eqsShuffleOutputBytesSpilled = Nothing
    , _eqsReadMsMax = Nothing
    , _eqsCompletedParallelInputs = Nothing
    , _eqsWaitRatioMax = Nothing
    , _eqsParallelInputs = Nothing
    , _eqsShuffleOutputBytes = Nothing
    , _eqsRecordsWritten = Nothing
    , _eqsSteps = Nothing
    , _eqsInputStages = Nothing
    , _eqsWriteRatioAvg = Nothing
    , _eqsRecordsRead = Nothing
    , _eqsComputeRatioAvg = Nothing
    , _eqsName = Nothing
    , _eqsComputeMsMax = Nothing
    , _eqsReadRatioMax = Nothing
    , _eqsWriteMsMax = Nothing
    , _eqsWaitRatioAvg = Nothing
    , _eqsWaitMsAvg = Nothing
    , _eqsId = Nothing
    , _eqsComputeRatioMax = Nothing
    , _eqsWriteRatioMax = Nothing
    , _eqsComputeMsAvg = Nothing
    , _eqsReadRatioAvg = Nothing
    , _eqsWriteMsAvg = Nothing
    , _eqsStartMs = Nothing
    , _eqsEndMs = Nothing
    , _eqsWaitMsMax = Nothing
    }
eqsReadMsAvg :: Lens' ExplainQueryStage (Maybe Int64)
eqsReadMsAvg
  = lens _eqsReadMsAvg (\ s a -> s{_eqsReadMsAvg = a})
      . mapping _Coerce
eqsStatus :: Lens' ExplainQueryStage (Maybe Text)
eqsStatus
  = lens _eqsStatus (\ s a -> s{_eqsStatus = a})
eqsShuffleOutputBytesSpilled :: Lens' ExplainQueryStage (Maybe Int64)
eqsShuffleOutputBytesSpilled
  = lens _eqsShuffleOutputBytesSpilled
      (\ s a -> s{_eqsShuffleOutputBytesSpilled = a})
      . mapping _Coerce
eqsReadMsMax :: Lens' ExplainQueryStage (Maybe Int64)
eqsReadMsMax
  = lens _eqsReadMsMax (\ s a -> s{_eqsReadMsMax = a})
      . mapping _Coerce
eqsCompletedParallelInputs :: Lens' ExplainQueryStage (Maybe Int64)
eqsCompletedParallelInputs
  = lens _eqsCompletedParallelInputs
      (\ s a -> s{_eqsCompletedParallelInputs = a})
      . mapping _Coerce
eqsWaitRatioMax :: Lens' ExplainQueryStage (Maybe Double)
eqsWaitRatioMax
  = lens _eqsWaitRatioMax
      (\ s a -> s{_eqsWaitRatioMax = a})
      . mapping _Coerce
eqsParallelInputs :: Lens' ExplainQueryStage (Maybe Int64)
eqsParallelInputs
  = lens _eqsParallelInputs
      (\ s a -> s{_eqsParallelInputs = a})
      . mapping _Coerce
eqsShuffleOutputBytes :: Lens' ExplainQueryStage (Maybe Int64)
eqsShuffleOutputBytes
  = lens _eqsShuffleOutputBytes
      (\ s a -> s{_eqsShuffleOutputBytes = a})
      . mapping _Coerce
eqsRecordsWritten :: Lens' ExplainQueryStage (Maybe Int64)
eqsRecordsWritten
  = lens _eqsRecordsWritten
      (\ s a -> s{_eqsRecordsWritten = a})
      . mapping _Coerce
eqsSteps :: Lens' ExplainQueryStage [ExplainQueryStep]
eqsSteps
  = lens _eqsSteps (\ s a -> s{_eqsSteps = a}) .
      _Default
      . _Coerce
eqsInputStages :: Lens' ExplainQueryStage [Int64]
eqsInputStages
  = lens _eqsInputStages
      (\ s a -> s{_eqsInputStages = a})
      . _Default
      . _Coerce
eqsWriteRatioAvg :: Lens' ExplainQueryStage (Maybe Double)
eqsWriteRatioAvg
  = lens _eqsWriteRatioAvg
      (\ s a -> s{_eqsWriteRatioAvg = a})
      . mapping _Coerce
eqsRecordsRead :: Lens' ExplainQueryStage (Maybe Int64)
eqsRecordsRead
  = lens _eqsRecordsRead
      (\ s a -> s{_eqsRecordsRead = a})
      . mapping _Coerce
eqsComputeRatioAvg :: Lens' ExplainQueryStage (Maybe Double)
eqsComputeRatioAvg
  = lens _eqsComputeRatioAvg
      (\ s a -> s{_eqsComputeRatioAvg = a})
      . mapping _Coerce
eqsName :: Lens' ExplainQueryStage (Maybe Text)
eqsName = lens _eqsName (\ s a -> s{_eqsName = a})
eqsComputeMsMax :: Lens' ExplainQueryStage (Maybe Int64)
eqsComputeMsMax
  = lens _eqsComputeMsMax
      (\ s a -> s{_eqsComputeMsMax = a})
      . mapping _Coerce
eqsReadRatioMax :: Lens' ExplainQueryStage (Maybe Double)
eqsReadRatioMax
  = lens _eqsReadRatioMax
      (\ s a -> s{_eqsReadRatioMax = a})
      . mapping _Coerce
eqsWriteMsMax :: Lens' ExplainQueryStage (Maybe Int64)
eqsWriteMsMax
  = lens _eqsWriteMsMax
      (\ s a -> s{_eqsWriteMsMax = a})
      . mapping _Coerce
eqsWaitRatioAvg :: Lens' ExplainQueryStage (Maybe Double)
eqsWaitRatioAvg
  = lens _eqsWaitRatioAvg
      (\ s a -> s{_eqsWaitRatioAvg = a})
      . mapping _Coerce
eqsWaitMsAvg :: Lens' ExplainQueryStage (Maybe Int64)
eqsWaitMsAvg
  = lens _eqsWaitMsAvg (\ s a -> s{_eqsWaitMsAvg = a})
      . mapping _Coerce
eqsId :: Lens' ExplainQueryStage (Maybe Int64)
eqsId
  = lens _eqsId (\ s a -> s{_eqsId = a}) .
      mapping _Coerce
eqsComputeRatioMax :: Lens' ExplainQueryStage (Maybe Double)
eqsComputeRatioMax
  = lens _eqsComputeRatioMax
      (\ s a -> s{_eqsComputeRatioMax = a})
      . mapping _Coerce
eqsWriteRatioMax :: Lens' ExplainQueryStage (Maybe Double)
eqsWriteRatioMax
  = lens _eqsWriteRatioMax
      (\ s a -> s{_eqsWriteRatioMax = a})
      . mapping _Coerce
eqsComputeMsAvg :: Lens' ExplainQueryStage (Maybe Int64)
eqsComputeMsAvg
  = lens _eqsComputeMsAvg
      (\ s a -> s{_eqsComputeMsAvg = a})
      . mapping _Coerce
eqsReadRatioAvg :: Lens' ExplainQueryStage (Maybe Double)
eqsReadRatioAvg
  = lens _eqsReadRatioAvg
      (\ s a -> s{_eqsReadRatioAvg = a})
      . mapping _Coerce
eqsWriteMsAvg :: Lens' ExplainQueryStage (Maybe Int64)
eqsWriteMsAvg
  = lens _eqsWriteMsAvg
      (\ s a -> s{_eqsWriteMsAvg = a})
      . mapping _Coerce
eqsStartMs :: Lens' ExplainQueryStage (Maybe Int64)
eqsStartMs
  = lens _eqsStartMs (\ s a -> s{_eqsStartMs = a}) .
      mapping _Coerce
eqsEndMs :: Lens' ExplainQueryStage (Maybe Int64)
eqsEndMs
  = lens _eqsEndMs (\ s a -> s{_eqsEndMs = a}) .
      mapping _Coerce
eqsWaitMsMax :: Lens' ExplainQueryStage (Maybe Int64)
eqsWaitMsMax
  = lens _eqsWaitMsMax (\ s a -> s{_eqsWaitMsMax = a})
      . mapping _Coerce
instance FromJSON ExplainQueryStage where
        parseJSON
          = withObject "ExplainQueryStage"
              (\ o ->
                 ExplainQueryStage' <$>
                   (o .:? "readMsAvg") <*> (o .:? "status") <*>
                     (o .:? "shuffleOutputBytesSpilled")
                     <*> (o .:? "readMsMax")
                     <*> (o .:? "completedParallelInputs")
                     <*> (o .:? "waitRatioMax")
                     <*> (o .:? "parallelInputs")
                     <*> (o .:? "shuffleOutputBytes")
                     <*> (o .:? "recordsWritten")
                     <*> (o .:? "steps" .!= mempty)
                     <*> (o .:? "inputStages" .!= mempty)
                     <*> (o .:? "writeRatioAvg")
                     <*> (o .:? "recordsRead")
                     <*> (o .:? "computeRatioAvg")
                     <*> (o .:? "name")
                     <*> (o .:? "computeMsMax")
                     <*> (o .:? "readRatioMax")
                     <*> (o .:? "writeMsMax")
                     <*> (o .:? "waitRatioAvg")
                     <*> (o .:? "waitMsAvg")
                     <*> (o .:? "id")
                     <*> (o .:? "computeRatioMax")
                     <*> (o .:? "writeRatioMax")
                     <*> (o .:? "computeMsAvg")
                     <*> (o .:? "readRatioAvg")
                     <*> (o .:? "writeMsAvg")
                     <*> (o .:? "startMs")
                     <*> (o .:? "endMs")
                     <*> (o .:? "waitMsMax"))
instance ToJSON ExplainQueryStage where
        toJSON ExplainQueryStage'{..}
          = object
              (catMaybes
                 [("readMsAvg" .=) <$> _eqsReadMsAvg,
                  ("status" .=) <$> _eqsStatus,
                  ("shuffleOutputBytesSpilled" .=) <$>
                    _eqsShuffleOutputBytesSpilled,
                  ("readMsMax" .=) <$> _eqsReadMsMax,
                  ("completedParallelInputs" .=) <$>
                    _eqsCompletedParallelInputs,
                  ("waitRatioMax" .=) <$> _eqsWaitRatioMax,
                  ("parallelInputs" .=) <$> _eqsParallelInputs,
                  ("shuffleOutputBytes" .=) <$> _eqsShuffleOutputBytes,
                  ("recordsWritten" .=) <$> _eqsRecordsWritten,
                  ("steps" .=) <$> _eqsSteps,
                  ("inputStages" .=) <$> _eqsInputStages,
                  ("writeRatioAvg" .=) <$> _eqsWriteRatioAvg,
                  ("recordsRead" .=) <$> _eqsRecordsRead,
                  ("computeRatioAvg" .=) <$> _eqsComputeRatioAvg,
                  ("name" .=) <$> _eqsName,
                  ("computeMsMax" .=) <$> _eqsComputeMsMax,
                  ("readRatioMax" .=) <$> _eqsReadRatioMax,
                  ("writeMsMax" .=) <$> _eqsWriteMsMax,
                  ("waitRatioAvg" .=) <$> _eqsWaitRatioAvg,
                  ("waitMsAvg" .=) <$> _eqsWaitMsAvg,
                  ("id" .=) <$> _eqsId,
                  ("computeRatioMax" .=) <$> _eqsComputeRatioMax,
                  ("writeRatioMax" .=) <$> _eqsWriteRatioMax,
                  ("computeMsAvg" .=) <$> _eqsComputeMsAvg,
                  ("readRatioAvg" .=) <$> _eqsReadRatioAvg,
                  ("writeMsAvg" .=) <$> _eqsWriteMsAvg,
                  ("startMs" .=) <$> _eqsStartMs,
                  ("endMs" .=) <$> _eqsEndMs,
                  ("waitMsMax" .=) <$> _eqsWaitMsMax])
data BigQueryModelTraining =
  BigQueryModelTraining'
    { _bqmtExpectedTotalIterations :: !(Maybe (Textual Int64))
    , _bqmtCurrentIteration        :: !(Maybe (Textual Int32))
    }
  deriving (Eq, Show, Data, Typeable, Generic)
bigQueryModelTraining
    :: BigQueryModelTraining
bigQueryModelTraining =
  BigQueryModelTraining'
    {_bqmtExpectedTotalIterations = Nothing, _bqmtCurrentIteration = Nothing}
bqmtExpectedTotalIterations :: Lens' BigQueryModelTraining (Maybe Int64)
bqmtExpectedTotalIterations
  = lens _bqmtExpectedTotalIterations
      (\ s a -> s{_bqmtExpectedTotalIterations = a})
      . mapping _Coerce
bqmtCurrentIteration :: Lens' BigQueryModelTraining (Maybe Int32)
bqmtCurrentIteration
  = lens _bqmtCurrentIteration
      (\ s a -> s{_bqmtCurrentIteration = a})
      . mapping _Coerce
instance FromJSON BigQueryModelTraining where
        parseJSON
          = withObject "BigQueryModelTraining"
              (\ o ->
                 BigQueryModelTraining' <$>
                   (o .:? "expectedTotalIterations") <*>
                     (o .:? "currentIteration"))
instance ToJSON BigQueryModelTraining where
        toJSON BigQueryModelTraining'{..}
          = object
              (catMaybes
                 [("expectedTotalIterations" .=) <$>
                    _bqmtExpectedTotalIterations,
                  ("currentIteration" .=) <$> _bqmtCurrentIteration])
data JobConfigurationLoad =
  JobConfigurationLoad'
    { _jclSkipLeadingRows                    :: !(Maybe (Textual Int32))
    , _jclProjectionFields                   :: !(Maybe [Text])
    , _jclDestinationTable                   :: !(Maybe TableReference)
    , _jclWriteDisPosition                   :: !(Maybe Text)
    , _jclAllowJaggedRows                    :: !(Maybe Bool)
    , _jclClustering                         :: !(Maybe Clustering)
    , _jclRangePartitioning                  :: !(Maybe RangePartitioning)
    , _jclSchemaInline                       :: !(Maybe Text)
    , _jclIgnoreUnknownValues                :: !(Maybe Bool)
    , _jclSchemaUpdateOptions                :: !(Maybe [Text])
    , _jclHivePartitioningMode               :: !(Maybe Text)
    , _jclCreateDisPosition                  :: !(Maybe Text)
    , _jclSchemaInlineFormat                 :: !(Maybe Text)
    , _jclAllowQuotedNewlines                :: !(Maybe Bool)
    , _jclSourceFormat                       :: !(Maybe Text)
    , _jclUseAvroLogicalTypes                :: !(Maybe Bool)
    , _jclSchema                             :: !(Maybe TableSchema)
    , _jclTimePartitioning                   :: !(Maybe TimePartitioning)
    , _jclQuote                              :: !(Maybe Text)
    , _jclMaxBadRecords                      :: !(Maybe (Textual Int32))
    , _jclAutodetect                         :: !(Maybe Bool)
    , _jclSourceURIs                         :: !(Maybe [Text])
    , _jclEncoding                           :: !(Maybe Text)
    , _jclDestinationTableProperties         :: !(Maybe DestinationTableProperties)
    , _jclDestinationEncryptionConfiguration :: !(Maybe EncryptionConfiguration)
    , _jclFieldDelimiter                     :: !(Maybe Text)
    , _jclNullMarker                         :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobConfigurationLoad
    :: JobConfigurationLoad
jobConfigurationLoad =
  JobConfigurationLoad'
    { _jclSkipLeadingRows = Nothing
    , _jclProjectionFields = Nothing
    , _jclDestinationTable = Nothing
    , _jclWriteDisPosition = Nothing
    , _jclAllowJaggedRows = Nothing
    , _jclClustering = Nothing
    , _jclRangePartitioning = Nothing
    , _jclSchemaInline = Nothing
    , _jclIgnoreUnknownValues = Nothing
    , _jclSchemaUpdateOptions = Nothing
    , _jclHivePartitioningMode = Nothing
    , _jclCreateDisPosition = Nothing
    , _jclSchemaInlineFormat = Nothing
    , _jclAllowQuotedNewlines = Nothing
    , _jclSourceFormat = Nothing
    , _jclUseAvroLogicalTypes = Nothing
    , _jclSchema = Nothing
    , _jclTimePartitioning = Nothing
    , _jclQuote = Nothing
    , _jclMaxBadRecords = Nothing
    , _jclAutodetect = Nothing
    , _jclSourceURIs = Nothing
    , _jclEncoding = Nothing
    , _jclDestinationTableProperties = Nothing
    , _jclDestinationEncryptionConfiguration = Nothing
    , _jclFieldDelimiter = Nothing
    , _jclNullMarker = Nothing
    }
jclSkipLeadingRows :: Lens' JobConfigurationLoad (Maybe Int32)
jclSkipLeadingRows
  = lens _jclSkipLeadingRows
      (\ s a -> s{_jclSkipLeadingRows = a})
      . mapping _Coerce
jclProjectionFields :: Lens' JobConfigurationLoad [Text]
jclProjectionFields
  = lens _jclProjectionFields
      (\ s a -> s{_jclProjectionFields = a})
      . _Default
      . _Coerce
jclDestinationTable :: Lens' JobConfigurationLoad (Maybe TableReference)
jclDestinationTable
  = lens _jclDestinationTable
      (\ s a -> s{_jclDestinationTable = a})
jclWriteDisPosition :: Lens' JobConfigurationLoad (Maybe Text)
jclWriteDisPosition
  = lens _jclWriteDisPosition
      (\ s a -> s{_jclWriteDisPosition = a})
jclAllowJaggedRows :: Lens' JobConfigurationLoad (Maybe Bool)
jclAllowJaggedRows
  = lens _jclAllowJaggedRows
      (\ s a -> s{_jclAllowJaggedRows = a})
jclClustering :: Lens' JobConfigurationLoad (Maybe Clustering)
jclClustering
  = lens _jclClustering
      (\ s a -> s{_jclClustering = a})
jclRangePartitioning :: Lens' JobConfigurationLoad (Maybe RangePartitioning)
jclRangePartitioning
  = lens _jclRangePartitioning
      (\ s a -> s{_jclRangePartitioning = a})
jclSchemaInline :: Lens' JobConfigurationLoad (Maybe Text)
jclSchemaInline
  = lens _jclSchemaInline
      (\ s a -> s{_jclSchemaInline = a})
jclIgnoreUnknownValues :: Lens' JobConfigurationLoad (Maybe Bool)
jclIgnoreUnknownValues
  = lens _jclIgnoreUnknownValues
      (\ s a -> s{_jclIgnoreUnknownValues = a})
jclSchemaUpdateOptions :: Lens' JobConfigurationLoad [Text]
jclSchemaUpdateOptions
  = lens _jclSchemaUpdateOptions
      (\ s a -> s{_jclSchemaUpdateOptions = a})
      . _Default
      . _Coerce
jclHivePartitioningMode :: Lens' JobConfigurationLoad (Maybe Text)
jclHivePartitioningMode
  = lens _jclHivePartitioningMode
      (\ s a -> s{_jclHivePartitioningMode = a})
jclCreateDisPosition :: Lens' JobConfigurationLoad (Maybe Text)
jclCreateDisPosition
  = lens _jclCreateDisPosition
      (\ s a -> s{_jclCreateDisPosition = a})
jclSchemaInlineFormat :: Lens' JobConfigurationLoad (Maybe Text)
jclSchemaInlineFormat
  = lens _jclSchemaInlineFormat
      (\ s a -> s{_jclSchemaInlineFormat = a})
jclAllowQuotedNewlines :: Lens' JobConfigurationLoad (Maybe Bool)
jclAllowQuotedNewlines
  = lens _jclAllowQuotedNewlines
      (\ s a -> s{_jclAllowQuotedNewlines = a})
jclSourceFormat :: Lens' JobConfigurationLoad (Maybe Text)
jclSourceFormat
  = lens _jclSourceFormat
      (\ s a -> s{_jclSourceFormat = a})
jclUseAvroLogicalTypes :: Lens' JobConfigurationLoad (Maybe Bool)
jclUseAvroLogicalTypes
  = lens _jclUseAvroLogicalTypes
      (\ s a -> s{_jclUseAvroLogicalTypes = a})
jclSchema :: Lens' JobConfigurationLoad (Maybe TableSchema)
jclSchema
  = lens _jclSchema (\ s a -> s{_jclSchema = a})
jclTimePartitioning :: Lens' JobConfigurationLoad (Maybe TimePartitioning)
jclTimePartitioning
  = lens _jclTimePartitioning
      (\ s a -> s{_jclTimePartitioning = a})
jclQuote :: Lens' JobConfigurationLoad (Maybe Text)
jclQuote = lens _jclQuote (\ s a -> s{_jclQuote = a})
jclMaxBadRecords :: Lens' JobConfigurationLoad (Maybe Int32)
jclMaxBadRecords
  = lens _jclMaxBadRecords
      (\ s a -> s{_jclMaxBadRecords = a})
      . mapping _Coerce
jclAutodetect :: Lens' JobConfigurationLoad (Maybe Bool)
jclAutodetect
  = lens _jclAutodetect
      (\ s a -> s{_jclAutodetect = a})
jclSourceURIs :: Lens' JobConfigurationLoad [Text]
jclSourceURIs
  = lens _jclSourceURIs
      (\ s a -> s{_jclSourceURIs = a})
      . _Default
      . _Coerce
jclEncoding :: Lens' JobConfigurationLoad (Maybe Text)
jclEncoding
  = lens _jclEncoding (\ s a -> s{_jclEncoding = a})
jclDestinationTableProperties :: Lens' JobConfigurationLoad (Maybe DestinationTableProperties)
jclDestinationTableProperties
  = lens _jclDestinationTableProperties
      (\ s a -> s{_jclDestinationTableProperties = a})
jclDestinationEncryptionConfiguration :: Lens' JobConfigurationLoad (Maybe EncryptionConfiguration)
jclDestinationEncryptionConfiguration
  = lens _jclDestinationEncryptionConfiguration
      (\ s a ->
         s{_jclDestinationEncryptionConfiguration = a})
jclFieldDelimiter :: Lens' JobConfigurationLoad (Maybe Text)
jclFieldDelimiter
  = lens _jclFieldDelimiter
      (\ s a -> s{_jclFieldDelimiter = a})
jclNullMarker :: Lens' JobConfigurationLoad (Maybe Text)
jclNullMarker
  = lens _jclNullMarker
      (\ s a -> s{_jclNullMarker = a})
instance FromJSON JobConfigurationLoad where
        parseJSON
          = withObject "JobConfigurationLoad"
              (\ o ->
                 JobConfigurationLoad' <$>
                   (o .:? "skipLeadingRows") <*>
                     (o .:? "projectionFields" .!= mempty)
                     <*> (o .:? "destinationTable")
                     <*> (o .:? "writeDisposition")
                     <*> (o .:? "allowJaggedRows")
                     <*> (o .:? "clustering")
                     <*> (o .:? "rangePartitioning")
                     <*> (o .:? "schemaInline")
                     <*> (o .:? "ignoreUnknownValues")
                     <*> (o .:? "schemaUpdateOptions" .!= mempty)
                     <*> (o .:? "hivePartitioningMode")
                     <*> (o .:? "createDisposition")
                     <*> (o .:? "schemaInlineFormat")
                     <*> (o .:? "allowQuotedNewlines")
                     <*> (o .:? "sourceFormat")
                     <*> (o .:? "useAvroLogicalTypes")
                     <*> (o .:? "schema")
                     <*> (o .:? "timePartitioning")
                     <*> (o .:? "quote")
                     <*> (o .:? "maxBadRecords")
                     <*> (o .:? "autodetect")
                     <*> (o .:? "sourceUris" .!= mempty)
                     <*> (o .:? "encoding")
                     <*> (o .:? "destinationTableProperties")
                     <*> (o .:? "destinationEncryptionConfiguration")
                     <*> (o .:? "fieldDelimiter")
                     <*> (o .:? "nullMarker"))
instance ToJSON JobConfigurationLoad where
        toJSON JobConfigurationLoad'{..}
          = object
              (catMaybes
                 [("skipLeadingRows" .=) <$> _jclSkipLeadingRows,
                  ("projectionFields" .=) <$> _jclProjectionFields,
                  ("destinationTable" .=) <$> _jclDestinationTable,
                  ("writeDisposition" .=) <$> _jclWriteDisPosition,
                  ("allowJaggedRows" .=) <$> _jclAllowJaggedRows,
                  ("clustering" .=) <$> _jclClustering,
                  ("rangePartitioning" .=) <$> _jclRangePartitioning,
                  ("schemaInline" .=) <$> _jclSchemaInline,
                  ("ignoreUnknownValues" .=) <$>
                    _jclIgnoreUnknownValues,
                  ("schemaUpdateOptions" .=) <$>
                    _jclSchemaUpdateOptions,
                  ("hivePartitioningMode" .=) <$>
                    _jclHivePartitioningMode,
                  ("createDisposition" .=) <$> _jclCreateDisPosition,
                  ("schemaInlineFormat" .=) <$> _jclSchemaInlineFormat,
                  ("allowQuotedNewlines" .=) <$>
                    _jclAllowQuotedNewlines,
                  ("sourceFormat" .=) <$> _jclSourceFormat,
                  ("useAvroLogicalTypes" .=) <$>
                    _jclUseAvroLogicalTypes,
                  ("schema" .=) <$> _jclSchema,
                  ("timePartitioning" .=) <$> _jclTimePartitioning,
                  ("quote" .=) <$> _jclQuote,
                  ("maxBadRecords" .=) <$> _jclMaxBadRecords,
                  ("autodetect" .=) <$> _jclAutodetect,
                  ("sourceUris" .=) <$> _jclSourceURIs,
                  ("encoding" .=) <$> _jclEncoding,
                  ("destinationTableProperties" .=) <$>
                    _jclDestinationTableProperties,
                  ("destinationEncryptionConfiguration" .=) <$>
                    _jclDestinationEncryptionConfiguration,
                  ("fieldDelimiter" .=) <$> _jclFieldDelimiter,
                  ("nullMarker" .=) <$> _jclNullMarker])
data DataSetReference =
  DataSetReference'
    { _dsrDataSetId :: !(Maybe Text)
    , _dsrProjectId :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
dataSetReference
    :: DataSetReference
dataSetReference =
  DataSetReference' {_dsrDataSetId = Nothing, _dsrProjectId = Nothing}
dsrDataSetId :: Lens' DataSetReference (Maybe Text)
dsrDataSetId
  = lens _dsrDataSetId (\ s a -> s{_dsrDataSetId = a})
dsrProjectId :: Lens' DataSetReference (Maybe Text)
dsrProjectId
  = lens _dsrProjectId (\ s a -> s{_dsrProjectId = a})
instance FromJSON DataSetReference where
        parseJSON
          = withObject "DataSetReference"
              (\ o ->
                 DataSetReference' <$>
                   (o .:? "datasetId") <*> (o .:? "projectId"))
instance ToJSON DataSetReference where
        toJSON DataSetReference'{..}
          = object
              (catMaybes
                 [("datasetId" .=) <$> _dsrDataSetId,
                  ("projectId" .=) <$> _dsrProjectId])
data MaterializedViewDefinition =
  MaterializedViewDefinition'
    { _mvdQuery           :: !(Maybe Text)
    , _mvdLastRefreshTime :: !(Maybe (Textual Int64))
    }
  deriving (Eq, Show, Data, Typeable, Generic)
materializedViewDefinition
    :: MaterializedViewDefinition
materializedViewDefinition =
  MaterializedViewDefinition'
    {_mvdQuery = Nothing, _mvdLastRefreshTime = Nothing}
mvdQuery :: Lens' MaterializedViewDefinition (Maybe Text)
mvdQuery = lens _mvdQuery (\ s a -> s{_mvdQuery = a})
mvdLastRefreshTime :: Lens' MaterializedViewDefinition (Maybe Int64)
mvdLastRefreshTime
  = lens _mvdLastRefreshTime
      (\ s a -> s{_mvdLastRefreshTime = a})
      . mapping _Coerce
instance FromJSON MaterializedViewDefinition where
        parseJSON
          = withObject "MaterializedViewDefinition"
              (\ o ->
                 MaterializedViewDefinition' <$>
                   (o .:? "query") <*> (o .:? "lastRefreshTime"))
instance ToJSON MaterializedViewDefinition where
        toJSON MaterializedViewDefinition'{..}
          = object
              (catMaybes
                 [("query" .=) <$> _mvdQuery,
                  ("lastRefreshTime" .=) <$> _mvdLastRefreshTime])
data TableDataInsertAllRequest =
  TableDataInsertAllRequest'
    { _tdiarKind                :: !Text
    , _tdiarIgnoreUnknownValues :: !(Maybe Bool)
    , _tdiarRows                :: !(Maybe [TableDataInsertAllRequestRowsItem])
    , _tdiarTemplateSuffix      :: !(Maybe Text)
    , _tdiarSkipInvalidRows     :: !(Maybe Bool)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
tableDataInsertAllRequest
    :: TableDataInsertAllRequest
tableDataInsertAllRequest =
  TableDataInsertAllRequest'
    { _tdiarKind = "bigquery#tableDataInsertAllRequest"
    , _tdiarIgnoreUnknownValues = Nothing
    , _tdiarRows = Nothing
    , _tdiarTemplateSuffix = Nothing
    , _tdiarSkipInvalidRows = Nothing
    }
tdiarKind :: Lens' TableDataInsertAllRequest Text
tdiarKind
  = lens _tdiarKind (\ s a -> s{_tdiarKind = a})
tdiarIgnoreUnknownValues :: Lens' TableDataInsertAllRequest (Maybe Bool)
tdiarIgnoreUnknownValues
  = lens _tdiarIgnoreUnknownValues
      (\ s a -> s{_tdiarIgnoreUnknownValues = a})
tdiarRows :: Lens' TableDataInsertAllRequest [TableDataInsertAllRequestRowsItem]
tdiarRows
  = lens _tdiarRows (\ s a -> s{_tdiarRows = a}) .
      _Default
      . _Coerce
tdiarTemplateSuffix :: Lens' TableDataInsertAllRequest (Maybe Text)
tdiarTemplateSuffix
  = lens _tdiarTemplateSuffix
      (\ s a -> s{_tdiarTemplateSuffix = a})
tdiarSkipInvalidRows :: Lens' TableDataInsertAllRequest (Maybe Bool)
tdiarSkipInvalidRows
  = lens _tdiarSkipInvalidRows
      (\ s a -> s{_tdiarSkipInvalidRows = a})
instance FromJSON TableDataInsertAllRequest where
        parseJSON
          = withObject "TableDataInsertAllRequest"
              (\ o ->
                 TableDataInsertAllRequest' <$>
                   (o .:? "kind" .!=
                      "bigquery#tableDataInsertAllRequest")
                     <*> (o .:? "ignoreUnknownValues")
                     <*> (o .:? "rows" .!= mempty)
                     <*> (o .:? "templateSuffix")
                     <*> (o .:? "skipInvalidRows"))
instance ToJSON TableDataInsertAllRequest where
        toJSON TableDataInsertAllRequest'{..}
          = object
              (catMaybes
                 [Just ("kind" .= _tdiarKind),
                  ("ignoreUnknownValues" .=) <$>
                    _tdiarIgnoreUnknownValues,
                  ("rows" .=) <$> _tdiarRows,
                  ("templateSuffix" .=) <$> _tdiarTemplateSuffix,
                  ("skipInvalidRows" .=) <$> _tdiarSkipInvalidRows])
data GetServiceAccountResponse =
  GetServiceAccountResponse'
    { _gsarEmail :: !(Maybe Text)
    , _gsarKind  :: !Text
    }
  deriving (Eq, Show, Data, Typeable, Generic)
getServiceAccountResponse
    :: GetServiceAccountResponse
getServiceAccountResponse =
  GetServiceAccountResponse'
    {_gsarEmail = Nothing, _gsarKind = "bigquery#getServiceAccountResponse"}
gsarEmail :: Lens' GetServiceAccountResponse (Maybe Text)
gsarEmail
  = lens _gsarEmail (\ s a -> s{_gsarEmail = a})
gsarKind :: Lens' GetServiceAccountResponse Text
gsarKind = lens _gsarKind (\ s a -> s{_gsarKind = a})
instance FromJSON GetServiceAccountResponse where
        parseJSON
          = withObject "GetServiceAccountResponse"
              (\ o ->
                 GetServiceAccountResponse' <$>
                   (o .:? "email") <*>
                     (o .:? "kind" .!=
                        "bigquery#getServiceAccountResponse"))
instance ToJSON GetServiceAccountResponse where
        toJSON GetServiceAccountResponse'{..}
          = object
              (catMaybes
                 [("email" .=) <$> _gsarEmail,
                  Just ("kind" .= _gsarKind)])
data ProjectListProjectsItem =
  ProjectListProjectsItem'
    { _plpiFriendlyName     :: !(Maybe Text)
    , _plpiKind             :: !Text
    , _plpiProjectReference :: !(Maybe ProjectReference)
    , _plpiId               :: !(Maybe Text)
    , _plpiNumericId        :: !(Maybe (Textual Word64))
    }
  deriving (Eq, Show, Data, Typeable, Generic)
projectListProjectsItem
    :: ProjectListProjectsItem
projectListProjectsItem =
  ProjectListProjectsItem'
    { _plpiFriendlyName = Nothing
    , _plpiKind = "bigquery#project"
    , _plpiProjectReference = Nothing
    , _plpiId = Nothing
    , _plpiNumericId = Nothing
    }
plpiFriendlyName :: Lens' ProjectListProjectsItem (Maybe Text)
plpiFriendlyName
  = lens _plpiFriendlyName
      (\ s a -> s{_plpiFriendlyName = a})
plpiKind :: Lens' ProjectListProjectsItem Text
plpiKind = lens _plpiKind (\ s a -> s{_plpiKind = a})
plpiProjectReference :: Lens' ProjectListProjectsItem (Maybe ProjectReference)
plpiProjectReference
  = lens _plpiProjectReference
      (\ s a -> s{_plpiProjectReference = a})
plpiId :: Lens' ProjectListProjectsItem (Maybe Text)
plpiId = lens _plpiId (\ s a -> s{_plpiId = a})
plpiNumericId :: Lens' ProjectListProjectsItem (Maybe Word64)
plpiNumericId
  = lens _plpiNumericId
      (\ s a -> s{_plpiNumericId = a})
      . mapping _Coerce
instance FromJSON ProjectListProjectsItem where
        parseJSON
          = withObject "ProjectListProjectsItem"
              (\ o ->
                 ProjectListProjectsItem' <$>
                   (o .:? "friendlyName") <*>
                     (o .:? "kind" .!= "bigquery#project")
                     <*> (o .:? "projectReference")
                     <*> (o .:? "id")
                     <*> (o .:? "numericId"))
instance ToJSON ProjectListProjectsItem where
        toJSON ProjectListProjectsItem'{..}
          = object
              (catMaybes
                 [("friendlyName" .=) <$> _plpiFriendlyName,
                  Just ("kind" .= _plpiKind),
                  ("projectReference" .=) <$> _plpiProjectReference,
                  ("id" .=) <$> _plpiId,
                  ("numericId" .=) <$> _plpiNumericId])
data BqmlIterationResult =
  BqmlIterationResult'
    { _birDurationMs   :: !(Maybe (Textual Int64))
    , _birLearnRate    :: !(Maybe (Textual Double))
    , _birEvalLoss     :: !(Maybe (Textual Double))
    , _birTrainingLoss :: !(Maybe (Textual Double))
    , _birIndex        :: !(Maybe (Textual Int32))
    }
  deriving (Eq, Show, Data, Typeable, Generic)
bqmlIterationResult
    :: BqmlIterationResult
bqmlIterationResult =
  BqmlIterationResult'
    { _birDurationMs = Nothing
    , _birLearnRate = Nothing
    , _birEvalLoss = Nothing
    , _birTrainingLoss = Nothing
    , _birIndex = Nothing
    }
birDurationMs :: Lens' BqmlIterationResult (Maybe Int64)
birDurationMs
  = lens _birDurationMs
      (\ s a -> s{_birDurationMs = a})
      . mapping _Coerce
birLearnRate :: Lens' BqmlIterationResult (Maybe Double)
birLearnRate
  = lens _birLearnRate (\ s a -> s{_birLearnRate = a})
      . mapping _Coerce
birEvalLoss :: Lens' BqmlIterationResult (Maybe Double)
birEvalLoss
  = lens _birEvalLoss (\ s a -> s{_birEvalLoss = a}) .
      mapping _Coerce
birTrainingLoss :: Lens' BqmlIterationResult (Maybe Double)
birTrainingLoss
  = lens _birTrainingLoss
      (\ s a -> s{_birTrainingLoss = a})
      . mapping _Coerce
birIndex :: Lens' BqmlIterationResult (Maybe Int32)
birIndex
  = lens _birIndex (\ s a -> s{_birIndex = a}) .
      mapping _Coerce
instance FromJSON BqmlIterationResult where
        parseJSON
          = withObject "BqmlIterationResult"
              (\ o ->
                 BqmlIterationResult' <$>
                   (o .:? "durationMs") <*> (o .:? "learnRate") <*>
                     (o .:? "evalLoss")
                     <*> (o .:? "trainingLoss")
                     <*> (o .:? "index"))
instance ToJSON BqmlIterationResult where
        toJSON BqmlIterationResult'{..}
          = object
              (catMaybes
                 [("durationMs" .=) <$> _birDurationMs,
                  ("learnRate" .=) <$> _birLearnRate,
                  ("evalLoss" .=) <$> _birEvalLoss,
                  ("trainingLoss" .=) <$> _birTrainingLoss,
                  ("index" .=) <$> _birIndex])
data BigtableColumn =
  BigtableColumn'
    { _bcQualifierEncoded :: !(Maybe Bytes)
    , _bcFieldName        :: !(Maybe Text)
    , _bcQualifierString  :: !(Maybe Text)
    , _bcOnlyReadLatest   :: !(Maybe Bool)
    , _bcType             :: !(Maybe Text)
    , _bcEncoding         :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
bigtableColumn
    :: BigtableColumn
bigtableColumn =
  BigtableColumn'
    { _bcQualifierEncoded = Nothing
    , _bcFieldName = Nothing
    , _bcQualifierString = Nothing
    , _bcOnlyReadLatest = Nothing
    , _bcType = Nothing
    , _bcEncoding = Nothing
    }
bcQualifierEncoded :: Lens' BigtableColumn (Maybe ByteString)
bcQualifierEncoded
  = lens _bcQualifierEncoded
      (\ s a -> s{_bcQualifierEncoded = a})
      . mapping _Bytes
bcFieldName :: Lens' BigtableColumn (Maybe Text)
bcFieldName
  = lens _bcFieldName (\ s a -> s{_bcFieldName = a})
bcQualifierString :: Lens' BigtableColumn (Maybe Text)
bcQualifierString
  = lens _bcQualifierString
      (\ s a -> s{_bcQualifierString = a})
bcOnlyReadLatest :: Lens' BigtableColumn (Maybe Bool)
bcOnlyReadLatest
  = lens _bcOnlyReadLatest
      (\ s a -> s{_bcOnlyReadLatest = a})
bcType :: Lens' BigtableColumn (Maybe Text)
bcType = lens _bcType (\ s a -> s{_bcType = a})
bcEncoding :: Lens' BigtableColumn (Maybe Text)
bcEncoding
  = lens _bcEncoding (\ s a -> s{_bcEncoding = a})
instance FromJSON BigtableColumn where
        parseJSON
          = withObject "BigtableColumn"
              (\ o ->
                 BigtableColumn' <$>
                   (o .:? "qualifierEncoded") <*> (o .:? "fieldName")
                     <*> (o .:? "qualifierString")
                     <*> (o .:? "onlyReadLatest")
                     <*> (o .:? "type")
                     <*> (o .:? "encoding"))
instance ToJSON BigtableColumn where
        toJSON BigtableColumn'{..}
          = object
              (catMaybes
                 [("qualifierEncoded" .=) <$> _bcQualifierEncoded,
                  ("fieldName" .=) <$> _bcFieldName,
                  ("qualifierString" .=) <$> _bcQualifierString,
                  ("onlyReadLatest" .=) <$> _bcOnlyReadLatest,
                  ("type" .=) <$> _bcType,
                  ("encoding" .=) <$> _bcEncoding])
data Streamingbuffer =
  Streamingbuffer'
    { _sEstimatedBytes  :: !(Maybe (Textual Word64))
    , _sOldestEntryTime :: !(Maybe (Textual Word64))
    , _sEstimatedRows   :: !(Maybe (Textual Word64))
    }
  deriving (Eq, Show, Data, Typeable, Generic)
streamingbuffer
    :: Streamingbuffer
streamingbuffer =
  Streamingbuffer'
    { _sEstimatedBytes = Nothing
    , _sOldestEntryTime = Nothing
    , _sEstimatedRows = Nothing
    }
sEstimatedBytes :: Lens' Streamingbuffer (Maybe Word64)
sEstimatedBytes
  = lens _sEstimatedBytes
      (\ s a -> s{_sEstimatedBytes = a})
      . mapping _Coerce
sOldestEntryTime :: Lens' Streamingbuffer (Maybe Word64)
sOldestEntryTime
  = lens _sOldestEntryTime
      (\ s a -> s{_sOldestEntryTime = a})
      . mapping _Coerce
sEstimatedRows :: Lens' Streamingbuffer (Maybe Word64)
sEstimatedRows
  = lens _sEstimatedRows
      (\ s a -> s{_sEstimatedRows = a})
      . mapping _Coerce
instance FromJSON Streamingbuffer where
        parseJSON
          = withObject "Streamingbuffer"
              (\ o ->
                 Streamingbuffer' <$>
                   (o .:? "estimatedBytes") <*>
                     (o .:? "oldestEntryTime")
                     <*> (o .:? "estimatedRows"))
instance ToJSON Streamingbuffer where
        toJSON Streamingbuffer'{..}
          = object
              (catMaybes
                 [("estimatedBytes" .=) <$> _sEstimatedBytes,
                  ("oldestEntryTime" .=) <$> _sOldestEntryTime,
                  ("estimatedRows" .=) <$> _sEstimatedRows])
newtype TableRow =
  TableRow'
    { _trF :: Maybe [TableCell]
    }
  deriving (Eq, Show, Data, Typeable, Generic)
tableRow
    :: TableRow
tableRow = TableRow' {_trF = Nothing}
trF :: Lens' TableRow [TableCell]
trF
  = lens _trF (\ s a -> s{_trF = a}) . _Default .
      _Coerce
instance FromJSON TableRow where
        parseJSON
          = withObject "TableRow"
              (\ o -> TableRow' <$> (o .:? "f" .!= mempty))
instance ToJSON TableRow where
        toJSON TableRow'{..}
          = object (catMaybes [("f" .=) <$> _trF])
data JobListJobsItem =
  JobListJobsItem'
    { _jljiJobReference  :: !(Maybe JobReference)
    , _jljiStatus        :: !(Maybe JobStatus)
    , _jljiState         :: !(Maybe Text)
    , _jljiUserEmail     :: !(Maybe Text)
    , _jljiKind          :: !Text
    , _jljiErrorResult   :: !(Maybe ErrorProto)
    , _jljiId            :: !(Maybe Text)
    , _jljiStatistics    :: !(Maybe JobStatistics)
    , _jljiConfiguration :: !(Maybe JobConfiguration)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobListJobsItem
    :: JobListJobsItem
jobListJobsItem =
  JobListJobsItem'
    { _jljiJobReference = Nothing
    , _jljiStatus = Nothing
    , _jljiState = Nothing
    , _jljiUserEmail = Nothing
    , _jljiKind = "bigquery#job"
    , _jljiErrorResult = Nothing
    , _jljiId = Nothing
    , _jljiStatistics = Nothing
    , _jljiConfiguration = Nothing
    }
jljiJobReference :: Lens' JobListJobsItem (Maybe JobReference)
jljiJobReference
  = lens _jljiJobReference
      (\ s a -> s{_jljiJobReference = a})
jljiStatus :: Lens' JobListJobsItem (Maybe JobStatus)
jljiStatus
  = lens _jljiStatus (\ s a -> s{_jljiStatus = a})
jljiState :: Lens' JobListJobsItem (Maybe Text)
jljiState
  = lens _jljiState (\ s a -> s{_jljiState = a})
jljiUserEmail :: Lens' JobListJobsItem (Maybe Text)
jljiUserEmail
  = lens _jljiUserEmail
      (\ s a -> s{_jljiUserEmail = a})
jljiKind :: Lens' JobListJobsItem Text
jljiKind = lens _jljiKind (\ s a -> s{_jljiKind = a})
jljiErrorResult :: Lens' JobListJobsItem (Maybe ErrorProto)
jljiErrorResult
  = lens _jljiErrorResult
      (\ s a -> s{_jljiErrorResult = a})
jljiId :: Lens' JobListJobsItem (Maybe Text)
jljiId = lens _jljiId (\ s a -> s{_jljiId = a})
jljiStatistics :: Lens' JobListJobsItem (Maybe JobStatistics)
jljiStatistics
  = lens _jljiStatistics
      (\ s a -> s{_jljiStatistics = a})
jljiConfiguration :: Lens' JobListJobsItem (Maybe JobConfiguration)
jljiConfiguration
  = lens _jljiConfiguration
      (\ s a -> s{_jljiConfiguration = a})
instance FromJSON JobListJobsItem where
        parseJSON
          = withObject "JobListJobsItem"
              (\ o ->
                 JobListJobsItem' <$>
                   (o .:? "jobReference") <*> (o .:? "status") <*>
                     (o .:? "state")
                     <*> (o .:? "user_email")
                     <*> (o .:? "kind" .!= "bigquery#job")
                     <*> (o .:? "errorResult")
                     <*> (o .:? "id")
                     <*> (o .:? "statistics")
                     <*> (o .:? "configuration"))
instance ToJSON JobListJobsItem where
        toJSON JobListJobsItem'{..}
          = object
              (catMaybes
                 [("jobReference" .=) <$> _jljiJobReference,
                  ("status" .=) <$> _jljiStatus,
                  ("state" .=) <$> _jljiState,
                  ("user_email" .=) <$> _jljiUserEmail,
                  Just ("kind" .= _jljiKind),
                  ("errorResult" .=) <$> _jljiErrorResult,
                  ("id" .=) <$> _jljiId,
                  ("statistics" .=) <$> _jljiStatistics,
                  ("configuration" .=) <$> _jljiConfiguration])
data TimePartitioning =
  TimePartitioning'
    { _tpField                  :: !(Maybe Text)
    , _tpExpirationMs           :: !(Maybe (Textual Int64))
    , _tpRequirePartitionFilter :: !(Maybe Bool)
    , _tpType                   :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
timePartitioning
    :: TimePartitioning
timePartitioning =
  TimePartitioning'
    { _tpField = Nothing
    , _tpExpirationMs = Nothing
    , _tpRequirePartitionFilter = Nothing
    , _tpType = Nothing
    }
tpField :: Lens' TimePartitioning (Maybe Text)
tpField = lens _tpField (\ s a -> s{_tpField = a})
tpExpirationMs :: Lens' TimePartitioning (Maybe Int64)
tpExpirationMs
  = lens _tpExpirationMs
      (\ s a -> s{_tpExpirationMs = a})
      . mapping _Coerce
tpRequirePartitionFilter :: Lens' TimePartitioning (Maybe Bool)
tpRequirePartitionFilter
  = lens _tpRequirePartitionFilter
      (\ s a -> s{_tpRequirePartitionFilter = a})
tpType :: Lens' TimePartitioning (Maybe Text)
tpType = lens _tpType (\ s a -> s{_tpType = a})
instance FromJSON TimePartitioning where
        parseJSON
          = withObject "TimePartitioning"
              (\ o ->
                 TimePartitioning' <$>
                   (o .:? "field") <*> (o .:? "expirationMs") <*>
                     (o .:? "requirePartitionFilter")
                     <*> (o .:? "type"))
instance ToJSON TimePartitioning where
        toJSON TimePartitioning'{..}
          = object
              (catMaybes
                 [("field" .=) <$> _tpField,
                  ("expirationMs" .=) <$> _tpExpirationMs,
                  ("requirePartitionFilter" .=) <$>
                    _tpRequirePartitionFilter,
                  ("type" .=) <$> _tpType])
newtype QueryParameterValueStructValues =
  QueryParameterValueStructValues'
    { _qpvsvAddtional :: HashMap Text QueryParameterValue
    }
  deriving (Eq, Show, Data, Typeable, Generic)
queryParameterValueStructValues
    :: HashMap Text QueryParameterValue 
    -> QueryParameterValueStructValues
queryParameterValueStructValues pQpvsvAddtional_ =
  QueryParameterValueStructValues'
    {_qpvsvAddtional = _Coerce # pQpvsvAddtional_}
qpvsvAddtional :: Lens' QueryParameterValueStructValues (HashMap Text QueryParameterValue)
qpvsvAddtional
  = lens _qpvsvAddtional
      (\ s a -> s{_qpvsvAddtional = a})
      . _Coerce
instance FromJSON QueryParameterValueStructValues
         where
        parseJSON
          = withObject "QueryParameterValueStructValues"
              (\ o ->
                 QueryParameterValueStructValues' <$>
                   (parseJSONObject o))
instance ToJSON QueryParameterValueStructValues where
        toJSON = toJSON . _qpvsvAddtional
newtype DataSetLabels =
  DataSetLabels'
    { _dslAddtional :: HashMap Text Text
    }
  deriving (Eq, Show, Data, Typeable, Generic)
dataSetLabels
    :: HashMap Text Text 
    -> DataSetLabels
dataSetLabels pDslAddtional_ =
  DataSetLabels' {_dslAddtional = _Coerce # pDslAddtional_}
dslAddtional :: Lens' DataSetLabels (HashMap Text Text)
dslAddtional
  = lens _dslAddtional (\ s a -> s{_dslAddtional = a})
      . _Coerce
instance FromJSON DataSetLabels where
        parseJSON
          = withObject "DataSetLabels"
              (\ o -> DataSetLabels' <$> (parseJSONObject o))
instance ToJSON DataSetLabels where
        toJSON = toJSON . _dslAddtional
data JobConfiguration =
  JobConfiguration'
    { _jcJobType      :: !(Maybe Text)
    , _jcCopy         :: !(Maybe JobConfigurationTableCopy)
    , _jcLoad         :: !(Maybe JobConfigurationLoad)
    , _jcQuery        :: !(Maybe JobConfigurationQuery)
    , _jcJobTimeoutMs :: !(Maybe (Textual Int64))
    , _jcExtract      :: !(Maybe JobConfigurationExtract)
    , _jcLabels       :: !(Maybe JobConfigurationLabels)
    , _jcDryRun       :: !(Maybe Bool)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobConfiguration
    :: JobConfiguration
jobConfiguration =
  JobConfiguration'
    { _jcJobType = Nothing
    , _jcCopy = Nothing
    , _jcLoad = Nothing
    , _jcQuery = Nothing
    , _jcJobTimeoutMs = Nothing
    , _jcExtract = Nothing
    , _jcLabels = Nothing
    , _jcDryRun = Nothing
    }
jcJobType :: Lens' JobConfiguration (Maybe Text)
jcJobType
  = lens _jcJobType (\ s a -> s{_jcJobType = a})
jcCopy :: Lens' JobConfiguration (Maybe JobConfigurationTableCopy)
jcCopy = lens _jcCopy (\ s a -> s{_jcCopy = a})
jcLoad :: Lens' JobConfiguration (Maybe JobConfigurationLoad)
jcLoad = lens _jcLoad (\ s a -> s{_jcLoad = a})
jcQuery :: Lens' JobConfiguration (Maybe JobConfigurationQuery)
jcQuery = lens _jcQuery (\ s a -> s{_jcQuery = a})
jcJobTimeoutMs :: Lens' JobConfiguration (Maybe Int64)
jcJobTimeoutMs
  = lens _jcJobTimeoutMs
      (\ s a -> s{_jcJobTimeoutMs = a})
      . mapping _Coerce
jcExtract :: Lens' JobConfiguration (Maybe JobConfigurationExtract)
jcExtract
  = lens _jcExtract (\ s a -> s{_jcExtract = a})
jcLabels :: Lens' JobConfiguration (Maybe JobConfigurationLabels)
jcLabels = lens _jcLabels (\ s a -> s{_jcLabels = a})
jcDryRun :: Lens' JobConfiguration (Maybe Bool)
jcDryRun = lens _jcDryRun (\ s a -> s{_jcDryRun = a})
instance FromJSON JobConfiguration where
        parseJSON
          = withObject "JobConfiguration"
              (\ o ->
                 JobConfiguration' <$>
                   (o .:? "jobType") <*> (o .:? "copy") <*>
                     (o .:? "load")
                     <*> (o .:? "query")
                     <*> (o .:? "jobTimeoutMs")
                     <*> (o .:? "extract")
                     <*> (o .:? "labels")
                     <*> (o .:? "dryRun"))
instance ToJSON JobConfiguration where
        toJSON JobConfiguration'{..}
          = object
              (catMaybes
                 [("jobType" .=) <$> _jcJobType,
                  ("copy" .=) <$> _jcCopy, ("load" .=) <$> _jcLoad,
                  ("query" .=) <$> _jcQuery,
                  ("jobTimeoutMs" .=) <$> _jcJobTimeoutMs,
                  ("extract" .=) <$> _jcExtract,
                  ("labels" .=) <$> _jcLabels,
                  ("dryRun" .=) <$> _jcDryRun])
data Job =
  Job'
    { _jJobReference  :: !(Maybe JobReference)
    , _jStatus        :: !(Maybe JobStatus)
    , _jEtag          :: !(Maybe Text)
    , _jUserEmail     :: !(Maybe Text)
    , _jKind          :: !Text
    , _jSelfLink      :: !(Maybe Text)
    , _jId            :: !(Maybe Text)
    , _jStatistics    :: !(Maybe JobStatistics)
    , _jConfiguration :: !(Maybe JobConfiguration)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
job
    :: Job
job =
  Job'
    { _jJobReference = Nothing
    , _jStatus = Nothing
    , _jEtag = Nothing
    , _jUserEmail = Nothing
    , _jKind = "bigquery#job"
    , _jSelfLink = Nothing
    , _jId = Nothing
    , _jStatistics = Nothing
    , _jConfiguration = Nothing
    }
jJobReference :: Lens' Job (Maybe JobReference)
jJobReference
  = lens _jJobReference
      (\ s a -> s{_jJobReference = a})
jStatus :: Lens' Job (Maybe JobStatus)
jStatus = lens _jStatus (\ s a -> s{_jStatus = a})
jEtag :: Lens' Job (Maybe Text)
jEtag = lens _jEtag (\ s a -> s{_jEtag = a})
jUserEmail :: Lens' Job (Maybe Text)
jUserEmail
  = lens _jUserEmail (\ s a -> s{_jUserEmail = a})
jKind :: Lens' Job Text
jKind = lens _jKind (\ s a -> s{_jKind = a})
jSelfLink :: Lens' Job (Maybe Text)
jSelfLink
  = lens _jSelfLink (\ s a -> s{_jSelfLink = a})
jId :: Lens' Job (Maybe Text)
jId = lens _jId (\ s a -> s{_jId = a})
jStatistics :: Lens' Job (Maybe JobStatistics)
jStatistics
  = lens _jStatistics (\ s a -> s{_jStatistics = a})
jConfiguration :: Lens' Job (Maybe JobConfiguration)
jConfiguration
  = lens _jConfiguration
      (\ s a -> s{_jConfiguration = a})
instance FromJSON Job where
        parseJSON
          = withObject "Job"
              (\ o ->
                 Job' <$>
                   (o .:? "jobReference") <*> (o .:? "status") <*>
                     (o .:? "etag")
                     <*> (o .:? "user_email")
                     <*> (o .:? "kind" .!= "bigquery#job")
                     <*> (o .:? "selfLink")
                     <*> (o .:? "id")
                     <*> (o .:? "statistics")
                     <*> (o .:? "configuration"))
instance ToJSON Job where
        toJSON Job'{..}
          = object
              (catMaybes
                 [("jobReference" .=) <$> _jJobReference,
                  ("status" .=) <$> _jStatus, ("etag" .=) <$> _jEtag,
                  ("user_email" .=) <$> _jUserEmail,
                  Just ("kind" .= _jKind),
                  ("selfLink" .=) <$> _jSelfLink, ("id" .=) <$> _jId,
                  ("statistics" .=) <$> _jStatistics,
                  ("configuration" .=) <$> _jConfiguration])
newtype EncryptionConfiguration =
  EncryptionConfiguration'
    { _ecKmsKeyName :: Maybe Text
    }
  deriving (Eq, Show, Data, Typeable, Generic)
encryptionConfiguration
    :: EncryptionConfiguration
encryptionConfiguration = EncryptionConfiguration' {_ecKmsKeyName = Nothing}
ecKmsKeyName :: Lens' EncryptionConfiguration (Maybe Text)
ecKmsKeyName
  = lens _ecKmsKeyName (\ s a -> s{_ecKmsKeyName = a})
instance FromJSON EncryptionConfiguration where
        parseJSON
          = withObject "EncryptionConfiguration"
              (\ o ->
                 EncryptionConfiguration' <$> (o .:? "kmsKeyName"))
instance ToJSON EncryptionConfiguration where
        toJSON EncryptionConfiguration'{..}
          = object
              (catMaybes [("kmsKeyName" .=) <$> _ecKmsKeyName])
data TableDataInsertAllResponseInsertErrorsItem =
  TableDataInsertAllResponseInsertErrorsItem'
    { _tdiarieiErrors :: !(Maybe [ErrorProto])
    , _tdiarieiIndex  :: !(Maybe (Textual Word32))
    }
  deriving (Eq, Show, Data, Typeable, Generic)
tableDataInsertAllResponseInsertErrorsItem
    :: TableDataInsertAllResponseInsertErrorsItem
tableDataInsertAllResponseInsertErrorsItem =
  TableDataInsertAllResponseInsertErrorsItem'
    {_tdiarieiErrors = Nothing, _tdiarieiIndex = Nothing}
tdiarieiErrors :: Lens' TableDataInsertAllResponseInsertErrorsItem [ErrorProto]
tdiarieiErrors
  = lens _tdiarieiErrors
      (\ s a -> s{_tdiarieiErrors = a})
      . _Default
      . _Coerce
tdiarieiIndex :: Lens' TableDataInsertAllResponseInsertErrorsItem (Maybe Word32)
tdiarieiIndex
  = lens _tdiarieiIndex
      (\ s a -> s{_tdiarieiIndex = a})
      . mapping _Coerce
instance FromJSON
           TableDataInsertAllResponseInsertErrorsItem
         where
        parseJSON
          = withObject
              "TableDataInsertAllResponseInsertErrorsItem"
              (\ o ->
                 TableDataInsertAllResponseInsertErrorsItem' <$>
                   (o .:? "errors" .!= mempty) <*> (o .:? "index"))
instance ToJSON
           TableDataInsertAllResponseInsertErrorsItem
         where
        toJSON
          TableDataInsertAllResponseInsertErrorsItem'{..}
          = object
              (catMaybes
                 [("errors" .=) <$> _tdiarieiErrors,
                  ("index" .=) <$> _tdiarieiIndex])
data JobConfigurationExtract =
  JobConfigurationExtract'
    { _jceDestinationFormat :: !(Maybe Text)
    , _jceSourceTable       :: !(Maybe TableReference)
    , _jcePrintHeader       :: !Bool
    , _jceCompression       :: !(Maybe Text)
    , _jceDestinationURIs   :: !(Maybe [Text])
    , _jceDestinationURI    :: !(Maybe Text)
    , _jceFieldDelimiter    :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobConfigurationExtract
    :: JobConfigurationExtract
jobConfigurationExtract =
  JobConfigurationExtract'
    { _jceDestinationFormat = Nothing
    , _jceSourceTable = Nothing
    , _jcePrintHeader = True
    , _jceCompression = Nothing
    , _jceDestinationURIs = Nothing
    , _jceDestinationURI = Nothing
    , _jceFieldDelimiter = Nothing
    }
jceDestinationFormat :: Lens' JobConfigurationExtract (Maybe Text)
jceDestinationFormat
  = lens _jceDestinationFormat
      (\ s a -> s{_jceDestinationFormat = a})
jceSourceTable :: Lens' JobConfigurationExtract (Maybe TableReference)
jceSourceTable
  = lens _jceSourceTable
      (\ s a -> s{_jceSourceTable = a})
jcePrintHeader :: Lens' JobConfigurationExtract Bool
jcePrintHeader
  = lens _jcePrintHeader
      (\ s a -> s{_jcePrintHeader = a})
jceCompression :: Lens' JobConfigurationExtract (Maybe Text)
jceCompression
  = lens _jceCompression
      (\ s a -> s{_jceCompression = a})
jceDestinationURIs :: Lens' JobConfigurationExtract [Text]
jceDestinationURIs
  = lens _jceDestinationURIs
      (\ s a -> s{_jceDestinationURIs = a})
      . _Default
      . _Coerce
jceDestinationURI :: Lens' JobConfigurationExtract (Maybe Text)
jceDestinationURI
  = lens _jceDestinationURI
      (\ s a -> s{_jceDestinationURI = a})
jceFieldDelimiter :: Lens' JobConfigurationExtract (Maybe Text)
jceFieldDelimiter
  = lens _jceFieldDelimiter
      (\ s a -> s{_jceFieldDelimiter = a})
instance FromJSON JobConfigurationExtract where
        parseJSON
          = withObject "JobConfigurationExtract"
              (\ o ->
                 JobConfigurationExtract' <$>
                   (o .:? "destinationFormat") <*> (o .:? "sourceTable")
                     <*> (o .:? "printHeader" .!= True)
                     <*> (o .:? "compression")
                     <*> (o .:? "destinationUris" .!= mempty)
                     <*> (o .:? "destinationUri")
                     <*> (o .:? "fieldDelimiter"))
instance ToJSON JobConfigurationExtract where
        toJSON JobConfigurationExtract'{..}
          = object
              (catMaybes
                 [("destinationFormat" .=) <$> _jceDestinationFormat,
                  ("sourceTable" .=) <$> _jceSourceTable,
                  Just ("printHeader" .= _jcePrintHeader),
                  ("compression" .=) <$> _jceCompression,
                  ("destinationUris" .=) <$> _jceDestinationURIs,
                  ("destinationUri" .=) <$> _jceDestinationURI,
                  ("fieldDelimiter" .=) <$> _jceFieldDelimiter])
data ModelDefinition =
  ModelDefinition'
    { _mdModelOptions :: !(Maybe ModelDefinitionModelOptions)
    , _mdTrainingRuns :: !(Maybe [BqmlTrainingRun])
    }
  deriving (Eq, Show, Data, Typeable, Generic)
modelDefinition
    :: ModelDefinition
modelDefinition =
  ModelDefinition' {_mdModelOptions = Nothing, _mdTrainingRuns = Nothing}
mdModelOptions :: Lens' ModelDefinition (Maybe ModelDefinitionModelOptions)
mdModelOptions
  = lens _mdModelOptions
      (\ s a -> s{_mdModelOptions = a})
mdTrainingRuns :: Lens' ModelDefinition [BqmlTrainingRun]
mdTrainingRuns
  = lens _mdTrainingRuns
      (\ s a -> s{_mdTrainingRuns = a})
      . _Default
      . _Coerce
instance FromJSON ModelDefinition where
        parseJSON
          = withObject "ModelDefinition"
              (\ o ->
                 ModelDefinition' <$>
                   (o .:? "modelOptions") <*>
                     (o .:? "trainingRuns" .!= mempty))
instance ToJSON ModelDefinition where
        toJSON ModelDefinition'{..}
          = object
              (catMaybes
                 [("modelOptions" .=) <$> _mdModelOptions,
                  ("trainingRuns" .=) <$> _mdTrainingRuns])
data JobCancelResponse =
  JobCancelResponse'
    { _jcrKind :: !Text
    , _jcrJob  :: !(Maybe Job)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobCancelResponse
    :: JobCancelResponse
jobCancelResponse =
  JobCancelResponse'
    {_jcrKind = "bigquery#jobCancelResponse", _jcrJob = Nothing}
jcrKind :: Lens' JobCancelResponse Text
jcrKind = lens _jcrKind (\ s a -> s{_jcrKind = a})
jcrJob :: Lens' JobCancelResponse (Maybe Job)
jcrJob = lens _jcrJob (\ s a -> s{_jcrJob = a})
instance FromJSON JobCancelResponse where
        parseJSON
          = withObject "JobCancelResponse"
              (\ o ->
                 JobCancelResponse' <$>
                   (o .:? "kind" .!= "bigquery#jobCancelResponse") <*>
                     (o .:? "job"))
instance ToJSON JobCancelResponse where
        toJSON JobCancelResponse'{..}
          = object
              (catMaybes
                 [Just ("kind" .= _jcrKind), ("job" .=) <$> _jcrJob])
newtype JSONObject =
  JSONObject'
    { _joAddtional :: HashMap Text JSONValue
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jsonObject
    :: HashMap Text JSONValue 
    -> JSONObject
jsonObject pJoAddtional_ = JSONObject' {_joAddtional = _Coerce # pJoAddtional_}
joAddtional :: Lens' JSONObject (HashMap Text JSONValue)
joAddtional
  = lens _joAddtional (\ s a -> s{_joAddtional = a}) .
      _Coerce
instance FromJSON JSONObject where
        parseJSON
          = withObject "JSONObject"
              (\ o -> JSONObject' <$> (parseJSONObject o))
instance ToJSON JSONObject where
        toJSON = toJSON . _joAddtional
data JobConfigurationQuery =
  JobConfigurationQuery'
    { _jcqDestinationTable                   :: !(Maybe TableReference)
    , _jcqWriteDisPosition                   :: !(Maybe Text)
    , _jcqPriority                           :: !(Maybe Text)
    , _jcqClustering                         :: !(Maybe Clustering)
    , _jcqRangePartitioning                  :: !(Maybe RangePartitioning)
    , _jcqUseQueryCache                      :: !Bool
    , _jcqPreserveNulls                      :: !(Maybe Bool)
    , _jcqTableDefinitions                   :: !(Maybe JobConfigurationQueryTableDefinitions)
    , _jcqQueryParameters                    :: !(Maybe [QueryParameter])
    , _jcqSchemaUpdateOptions                :: !(Maybe [Text])
    , _jcqMaximumBytesBilled                 :: !(Maybe (Textual Int64))
    , _jcqCreateDisPosition                  :: !(Maybe Text)
    , _jcqUserDefinedFunctionResources       :: !(Maybe [UserDefinedFunctionResource])
    , _jcqAllowLargeResults                  :: !Bool
    , _jcqMaximumBillingTier                 :: !(Textual Int32)
    , _jcqTimePartitioning                   :: !(Maybe TimePartitioning)
    , _jcqQuery                              :: !(Maybe Text)
    , _jcqFlattenResults                     :: !Bool
    , _jcqParameterMode                      :: !(Maybe Text)
    , _jcqUseLegacySQL                       :: !Bool
    , _jcqDestinationEncryptionConfiguration :: !(Maybe EncryptionConfiguration)
    , _jcqDefaultDataSet                     :: !(Maybe DataSetReference)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobConfigurationQuery
    :: JobConfigurationQuery
jobConfigurationQuery =
  JobConfigurationQuery'
    { _jcqDestinationTable = Nothing
    , _jcqWriteDisPosition = Nothing
    , _jcqPriority = Nothing
    , _jcqClustering = Nothing
    , _jcqRangePartitioning = Nothing
    , _jcqUseQueryCache = True
    , _jcqPreserveNulls = Nothing
    , _jcqTableDefinitions = Nothing
    , _jcqQueryParameters = Nothing
    , _jcqSchemaUpdateOptions = Nothing
    , _jcqMaximumBytesBilled = Nothing
    , _jcqCreateDisPosition = Nothing
    , _jcqUserDefinedFunctionResources = Nothing
    , _jcqAllowLargeResults = False
    , _jcqMaximumBillingTier = 1
    , _jcqTimePartitioning = Nothing
    , _jcqQuery = Nothing
    , _jcqFlattenResults = True
    , _jcqParameterMode = Nothing
    , _jcqUseLegacySQL = True
    , _jcqDestinationEncryptionConfiguration = Nothing
    , _jcqDefaultDataSet = Nothing
    }
jcqDestinationTable :: Lens' JobConfigurationQuery (Maybe TableReference)
jcqDestinationTable
  = lens _jcqDestinationTable
      (\ s a -> s{_jcqDestinationTable = a})
jcqWriteDisPosition :: Lens' JobConfigurationQuery (Maybe Text)
jcqWriteDisPosition
  = lens _jcqWriteDisPosition
      (\ s a -> s{_jcqWriteDisPosition = a})
jcqPriority :: Lens' JobConfigurationQuery (Maybe Text)
jcqPriority
  = lens _jcqPriority (\ s a -> s{_jcqPriority = a})
jcqClustering :: Lens' JobConfigurationQuery (Maybe Clustering)
jcqClustering
  = lens _jcqClustering
      (\ s a -> s{_jcqClustering = a})
jcqRangePartitioning :: Lens' JobConfigurationQuery (Maybe RangePartitioning)
jcqRangePartitioning
  = lens _jcqRangePartitioning
      (\ s a -> s{_jcqRangePartitioning = a})
jcqUseQueryCache :: Lens' JobConfigurationQuery Bool
jcqUseQueryCache
  = lens _jcqUseQueryCache
      (\ s a -> s{_jcqUseQueryCache = a})
jcqPreserveNulls :: Lens' JobConfigurationQuery (Maybe Bool)
jcqPreserveNulls
  = lens _jcqPreserveNulls
      (\ s a -> s{_jcqPreserveNulls = a})
jcqTableDefinitions :: Lens' JobConfigurationQuery (Maybe JobConfigurationQueryTableDefinitions)
jcqTableDefinitions
  = lens _jcqTableDefinitions
      (\ s a -> s{_jcqTableDefinitions = a})
jcqQueryParameters :: Lens' JobConfigurationQuery [QueryParameter]
jcqQueryParameters
  = lens _jcqQueryParameters
      (\ s a -> s{_jcqQueryParameters = a})
      . _Default
      . _Coerce
jcqSchemaUpdateOptions :: Lens' JobConfigurationQuery [Text]
jcqSchemaUpdateOptions
  = lens _jcqSchemaUpdateOptions
      (\ s a -> s{_jcqSchemaUpdateOptions = a})
      . _Default
      . _Coerce
jcqMaximumBytesBilled :: Lens' JobConfigurationQuery (Maybe Int64)
jcqMaximumBytesBilled
  = lens _jcqMaximumBytesBilled
      (\ s a -> s{_jcqMaximumBytesBilled = a})
      . mapping _Coerce
jcqCreateDisPosition :: Lens' JobConfigurationQuery (Maybe Text)
jcqCreateDisPosition
  = lens _jcqCreateDisPosition
      (\ s a -> s{_jcqCreateDisPosition = a})
jcqUserDefinedFunctionResources :: Lens' JobConfigurationQuery [UserDefinedFunctionResource]
jcqUserDefinedFunctionResources
  = lens _jcqUserDefinedFunctionResources
      (\ s a -> s{_jcqUserDefinedFunctionResources = a})
      . _Default
      . _Coerce
jcqAllowLargeResults :: Lens' JobConfigurationQuery Bool
jcqAllowLargeResults
  = lens _jcqAllowLargeResults
      (\ s a -> s{_jcqAllowLargeResults = a})
jcqMaximumBillingTier :: Lens' JobConfigurationQuery Int32
jcqMaximumBillingTier
  = lens _jcqMaximumBillingTier
      (\ s a -> s{_jcqMaximumBillingTier = a})
      . _Coerce
jcqTimePartitioning :: Lens' JobConfigurationQuery (Maybe TimePartitioning)
jcqTimePartitioning
  = lens _jcqTimePartitioning
      (\ s a -> s{_jcqTimePartitioning = a})
jcqQuery :: Lens' JobConfigurationQuery (Maybe Text)
jcqQuery = lens _jcqQuery (\ s a -> s{_jcqQuery = a})
jcqFlattenResults :: Lens' JobConfigurationQuery Bool
jcqFlattenResults
  = lens _jcqFlattenResults
      (\ s a -> s{_jcqFlattenResults = a})
jcqParameterMode :: Lens' JobConfigurationQuery (Maybe Text)
jcqParameterMode
  = lens _jcqParameterMode
      (\ s a -> s{_jcqParameterMode = a})
jcqUseLegacySQL :: Lens' JobConfigurationQuery Bool
jcqUseLegacySQL
  = lens _jcqUseLegacySQL
      (\ s a -> s{_jcqUseLegacySQL = a})
jcqDestinationEncryptionConfiguration :: Lens' JobConfigurationQuery (Maybe EncryptionConfiguration)
jcqDestinationEncryptionConfiguration
  = lens _jcqDestinationEncryptionConfiguration
      (\ s a ->
         s{_jcqDestinationEncryptionConfiguration = a})
jcqDefaultDataSet :: Lens' JobConfigurationQuery (Maybe DataSetReference)
jcqDefaultDataSet
  = lens _jcqDefaultDataSet
      (\ s a -> s{_jcqDefaultDataSet = a})
instance FromJSON JobConfigurationQuery where
        parseJSON
          = withObject "JobConfigurationQuery"
              (\ o ->
                 JobConfigurationQuery' <$>
                   (o .:? "destinationTable") <*>
                     (o .:? "writeDisposition")
                     <*> (o .:? "priority")
                     <*> (o .:? "clustering")
                     <*> (o .:? "rangePartitioning")
                     <*> (o .:? "useQueryCache" .!= True)
                     <*> (o .:? "preserveNulls")
                     <*> (o .:? "tableDefinitions")
                     <*> (o .:? "queryParameters" .!= mempty)
                     <*> (o .:? "schemaUpdateOptions" .!= mempty)
                     <*> (o .:? "maximumBytesBilled")
                     <*> (o .:? "createDisposition")
                     <*> (o .:? "userDefinedFunctionResources" .!= mempty)
                     <*> (o .:? "allowLargeResults" .!= False)
                     <*> (o .:? "maximumBillingTier" .!= 1)
                     <*> (o .:? "timePartitioning")
                     <*> (o .:? "query")
                     <*> (o .:? "flattenResults" .!= True)
                     <*> (o .:? "parameterMode")
                     <*> (o .:? "useLegacySql" .!= True)
                     <*> (o .:? "destinationEncryptionConfiguration")
                     <*> (o .:? "defaultDataset"))
instance ToJSON JobConfigurationQuery where
        toJSON JobConfigurationQuery'{..}
          = object
              (catMaybes
                 [("destinationTable" .=) <$> _jcqDestinationTable,
                  ("writeDisposition" .=) <$> _jcqWriteDisPosition,
                  ("priority" .=) <$> _jcqPriority,
                  ("clustering" .=) <$> _jcqClustering,
                  ("rangePartitioning" .=) <$> _jcqRangePartitioning,
                  Just ("useQueryCache" .= _jcqUseQueryCache),
                  ("preserveNulls" .=) <$> _jcqPreserveNulls,
                  ("tableDefinitions" .=) <$> _jcqTableDefinitions,
                  ("queryParameters" .=) <$> _jcqQueryParameters,
                  ("schemaUpdateOptions" .=) <$>
                    _jcqSchemaUpdateOptions,
                  ("maximumBytesBilled" .=) <$> _jcqMaximumBytesBilled,
                  ("createDisposition" .=) <$> _jcqCreateDisPosition,
                  ("userDefinedFunctionResources" .=) <$>
                    _jcqUserDefinedFunctionResources,
                  Just ("allowLargeResults" .= _jcqAllowLargeResults),
                  Just
                    ("maximumBillingTier" .= _jcqMaximumBillingTier),
                  ("timePartitioning" .=) <$> _jcqTimePartitioning,
                  ("query" .=) <$> _jcqQuery,
                  Just ("flattenResults" .= _jcqFlattenResults),
                  ("parameterMode" .=) <$> _jcqParameterMode,
                  Just ("useLegacySql" .= _jcqUseLegacySQL),
                  ("destinationEncryptionConfiguration" .=) <$>
                    _jcqDestinationEncryptionConfiguration,
                  ("defaultDataset" .=) <$> _jcqDefaultDataSet])
data GoogleSheetsOptions =
  GoogleSheetsOptions'
    { _gsoSkipLeadingRows :: !(Maybe (Textual Int64))
    , _gsoRange           :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
googleSheetsOptions
    :: GoogleSheetsOptions
googleSheetsOptions =
  GoogleSheetsOptions' {_gsoSkipLeadingRows = Nothing, _gsoRange = Nothing}
gsoSkipLeadingRows :: Lens' GoogleSheetsOptions (Maybe Int64)
gsoSkipLeadingRows
  = lens _gsoSkipLeadingRows
      (\ s a -> s{_gsoSkipLeadingRows = a})
      . mapping _Coerce
gsoRange :: Lens' GoogleSheetsOptions (Maybe Text)
gsoRange = lens _gsoRange (\ s a -> s{_gsoRange = a})
instance FromJSON GoogleSheetsOptions where
        parseJSON
          = withObject "GoogleSheetsOptions"
              (\ o ->
                 GoogleSheetsOptions' <$>
                   (o .:? "skipLeadingRows") <*> (o .:? "range"))
instance ToJSON GoogleSheetsOptions where
        toJSON GoogleSheetsOptions'{..}
          = object
              (catMaybes
                 [("skipLeadingRows" .=) <$> _gsoSkipLeadingRows,
                  ("range" .=) <$> _gsoRange])
data TableDataInsertAllRequestRowsItem =
  TableDataInsertAllRequestRowsItem'
    { _tdiarriJSON     :: !(Maybe JSONObject)
    , _tdiarriInsertId :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
tableDataInsertAllRequestRowsItem
    :: TableDataInsertAllRequestRowsItem
tableDataInsertAllRequestRowsItem =
  TableDataInsertAllRequestRowsItem'
    {_tdiarriJSON = Nothing, _tdiarriInsertId = Nothing}
tdiarriJSON :: Lens' TableDataInsertAllRequestRowsItem (Maybe JSONObject)
tdiarriJSON
  = lens _tdiarriJSON (\ s a -> s{_tdiarriJSON = a})
tdiarriInsertId :: Lens' TableDataInsertAllRequestRowsItem (Maybe Text)
tdiarriInsertId
  = lens _tdiarriInsertId
      (\ s a -> s{_tdiarriInsertId = a})
instance FromJSON TableDataInsertAllRequestRowsItem
         where
        parseJSON
          = withObject "TableDataInsertAllRequestRowsItem"
              (\ o ->
                 TableDataInsertAllRequestRowsItem' <$>
                   (o .:? "json") <*> (o .:? "insertId"))
instance ToJSON TableDataInsertAllRequestRowsItem
         where
        toJSON TableDataInsertAllRequestRowsItem'{..}
          = object
              (catMaybes
                 [("json" .=) <$> _tdiarriJSON,
                  ("insertId" .=) <$> _tdiarriInsertId])
data JobList =
  JobList'
    { _jlEtag          :: !(Maybe Text)
    , _jlNextPageToken :: !(Maybe Text)
    , _jlKind          :: !Text
    , _jlJobs          :: !(Maybe [JobListJobsItem])
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobList
    :: JobList
jobList =
  JobList'
    { _jlEtag = Nothing
    , _jlNextPageToken = Nothing
    , _jlKind = "bigquery#jobList"
    , _jlJobs = Nothing
    }
jlEtag :: Lens' JobList (Maybe Text)
jlEtag = lens _jlEtag (\ s a -> s{_jlEtag = a})
jlNextPageToken :: Lens' JobList (Maybe Text)
jlNextPageToken
  = lens _jlNextPageToken
      (\ s a -> s{_jlNextPageToken = a})
jlKind :: Lens' JobList Text
jlKind = lens _jlKind (\ s a -> s{_jlKind = a})
jlJobs :: Lens' JobList [JobListJobsItem]
jlJobs
  = lens _jlJobs (\ s a -> s{_jlJobs = a}) . _Default .
      _Coerce
instance FromJSON JobList where
        parseJSON
          = withObject "JobList"
              (\ o ->
                 JobList' <$>
                   (o .:? "etag") <*> (o .:? "nextPageToken") <*>
                     (o .:? "kind" .!= "bigquery#jobList")
                     <*> (o .:? "jobs" .!= mempty))
instance ToJSON JobList where
        toJSON JobList'{..}
          = object
              (catMaybes
                 [("etag" .=) <$> _jlEtag,
                  ("nextPageToken" .=) <$> _jlNextPageToken,
                  Just ("kind" .= _jlKind), ("jobs" .=) <$> _jlJobs])
newtype JobConfigurationQueryTableDefinitions =
  JobConfigurationQueryTableDefinitions'
    { _jcqtdAddtional :: HashMap Text ExternalDataConfiguration
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobConfigurationQueryTableDefinitions
    :: HashMap Text ExternalDataConfiguration 
    -> JobConfigurationQueryTableDefinitions
jobConfigurationQueryTableDefinitions pJcqtdAddtional_ =
  JobConfigurationQueryTableDefinitions'
    {_jcqtdAddtional = _Coerce # pJcqtdAddtional_}
jcqtdAddtional :: Lens' JobConfigurationQueryTableDefinitions (HashMap Text ExternalDataConfiguration)
jcqtdAddtional
  = lens _jcqtdAddtional
      (\ s a -> s{_jcqtdAddtional = a})
      . _Coerce
instance FromJSON
           JobConfigurationQueryTableDefinitions
         where
        parseJSON
          = withObject "JobConfigurationQueryTableDefinitions"
              (\ o ->
                 JobConfigurationQueryTableDefinitions' <$>
                   (parseJSONObject o))
instance ToJSON JobConfigurationQueryTableDefinitions
         where
        toJSON = toJSON . _jcqtdAddtional
newtype TableCell =
  TableCell'
    { _tcV :: Maybe JSONValue
    }
  deriving (Eq, Show, Data, Typeable, Generic)
tableCell
    :: TableCell
tableCell = TableCell' {_tcV = Nothing}
tcV :: Lens' TableCell (Maybe JSONValue)
tcV = lens _tcV (\ s a -> s{_tcV = a})
instance FromJSON TableCell where
        parseJSON
          = withObject "TableCell"
              (\ o -> TableCell' <$> (o .:? "v"))
instance ToJSON TableCell where
        toJSON TableCell'{..}
          = object (catMaybes [("v" .=) <$> _tcV])
data JobStatistics2ReservationUsageItem =
  JobStatistics2ReservationUsageItem'
    { _jName   :: !(Maybe Text)
    , _jSlotMs :: !(Maybe (Textual Int64))
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobStatistics2ReservationUsageItem
    :: JobStatistics2ReservationUsageItem
jobStatistics2ReservationUsageItem =
  JobStatistics2ReservationUsageItem' {_jName = Nothing, _jSlotMs = Nothing}
jName :: Lens' JobStatistics2ReservationUsageItem (Maybe Text)
jName = lens _jName (\ s a -> s{_jName = a})
jSlotMs :: Lens' JobStatistics2ReservationUsageItem (Maybe Int64)
jSlotMs
  = lens _jSlotMs (\ s a -> s{_jSlotMs = a}) .
      mapping _Coerce
instance FromJSON JobStatistics2ReservationUsageItem
         where
        parseJSON
          = withObject "JobStatistics2ReservationUsageItem"
              (\ o ->
                 JobStatistics2ReservationUsageItem' <$>
                   (o .:? "name") <*> (o .:? "slotMs"))
instance ToJSON JobStatistics2ReservationUsageItem
         where
        toJSON JobStatistics2ReservationUsageItem'{..}
          = object
              (catMaybes
                 [("name" .=) <$> _jName, ("slotMs" .=) <$> _jSlotMs])
data QueryParameterValue =
  QueryParameterValue'
    { _qpvStructValues :: !(Maybe QueryParameterValueStructValues)
    , _qpvValue        :: !(Maybe Text)
    , _qpvArrayValues  :: !(Maybe [QueryParameterValue])
    }
  deriving (Eq, Show, Data, Typeable, Generic)
queryParameterValue
    :: QueryParameterValue
queryParameterValue =
  QueryParameterValue'
    {_qpvStructValues = Nothing, _qpvValue = Nothing, _qpvArrayValues = Nothing}
qpvStructValues :: Lens' QueryParameterValue (Maybe QueryParameterValueStructValues)
qpvStructValues
  = lens _qpvStructValues
      (\ s a -> s{_qpvStructValues = a})
qpvValue :: Lens' QueryParameterValue (Maybe Text)
qpvValue = lens _qpvValue (\ s a -> s{_qpvValue = a})
qpvArrayValues :: Lens' QueryParameterValue [QueryParameterValue]
qpvArrayValues
  = lens _qpvArrayValues
      (\ s a -> s{_qpvArrayValues = a})
      . _Default
      . _Coerce
instance FromJSON QueryParameterValue where
        parseJSON
          = withObject "QueryParameterValue"
              (\ o ->
                 QueryParameterValue' <$>
                   (o .:? "structValues") <*> (o .:? "value") <*>
                     (o .:? "arrayValues" .!= mempty))
instance ToJSON QueryParameterValue where
        toJSON QueryParameterValue'{..}
          = object
              (catMaybes
                 [("structValues" .=) <$> _qpvStructValues,
                  ("value" .=) <$> _qpvValue,
                  ("arrayValues" .=) <$> _qpvArrayValues])
data ViewDefinition =
  ViewDefinition'
    { _vdUserDefinedFunctionResources :: !(Maybe [UserDefinedFunctionResource])
    , _vdQuery                        :: !(Maybe Text)
    , _vdUseLegacySQL                 :: !(Maybe Bool)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
viewDefinition
    :: ViewDefinition
viewDefinition =
  ViewDefinition'
    { _vdUserDefinedFunctionResources = Nothing
    , _vdQuery = Nothing
    , _vdUseLegacySQL = Nothing
    }
vdUserDefinedFunctionResources :: Lens' ViewDefinition [UserDefinedFunctionResource]
vdUserDefinedFunctionResources
  = lens _vdUserDefinedFunctionResources
      (\ s a -> s{_vdUserDefinedFunctionResources = a})
      . _Default
      . _Coerce
vdQuery :: Lens' ViewDefinition (Maybe Text)
vdQuery = lens _vdQuery (\ s a -> s{_vdQuery = a})
vdUseLegacySQL :: Lens' ViewDefinition (Maybe Bool)
vdUseLegacySQL
  = lens _vdUseLegacySQL
      (\ s a -> s{_vdUseLegacySQL = a})
instance FromJSON ViewDefinition where
        parseJSON
          = withObject "ViewDefinition"
              (\ o ->
                 ViewDefinition' <$>
                   (o .:? "userDefinedFunctionResources" .!= mempty) <*>
                     (o .:? "query")
                     <*> (o .:? "useLegacySql"))
instance ToJSON ViewDefinition where
        toJSON ViewDefinition'{..}
          = object
              (catMaybes
                 [("userDefinedFunctionResources" .=) <$>
                    _vdUserDefinedFunctionResources,
                  ("query" .=) <$> _vdQuery,
                  ("useLegacySql" .=) <$> _vdUseLegacySQL])
data UserDefinedFunctionResource =
  UserDefinedFunctionResource'
    { _udfrResourceURI :: !(Maybe Text)
    , _udfrInlineCode  :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
userDefinedFunctionResource
    :: UserDefinedFunctionResource
userDefinedFunctionResource =
  UserDefinedFunctionResource'
    {_udfrResourceURI = Nothing, _udfrInlineCode = Nothing}
udfrResourceURI :: Lens' UserDefinedFunctionResource (Maybe Text)
udfrResourceURI
  = lens _udfrResourceURI
      (\ s a -> s{_udfrResourceURI = a})
udfrInlineCode :: Lens' UserDefinedFunctionResource (Maybe Text)
udfrInlineCode
  = lens _udfrInlineCode
      (\ s a -> s{_udfrInlineCode = a})
instance FromJSON UserDefinedFunctionResource where
        parseJSON
          = withObject "UserDefinedFunctionResource"
              (\ o ->
                 UserDefinedFunctionResource' <$>
                   (o .:? "resourceUri") <*> (o .:? "inlineCode"))
instance ToJSON UserDefinedFunctionResource where
        toJSON UserDefinedFunctionResource'{..}
          = object
              (catMaybes
                 [("resourceUri" .=) <$> _udfrResourceURI,
                  ("inlineCode" .=) <$> _udfrInlineCode])
data JobStatistics2 =
  JobStatistics2'
    { _jModelTrainingExpectedTotalIteration :: !(Maybe (Textual Int64))
    , _jModelTraining                       :: !(Maybe BigQueryModelTraining)
    , _jTotalSlotMs                         :: !(Maybe (Textual Int64))
    , _jDdlTargetRoutine                    :: !(Maybe RoutineReference)
    , _jDdlTargetTable                      :: !(Maybe TableReference)
    , _jEstimatedBytesProcessed             :: !(Maybe (Textual Int64))
    , _jModelTrainingCurrentIteration       :: !(Maybe (Textual Int32))
    , _jSchema                              :: !(Maybe TableSchema)
    , _jTotalBytesProcessed                 :: !(Maybe (Textual Int64))
    , _jBillingTier                         :: !(Maybe (Textual Int32))
    , _jTotalBytesProcessedAccuracy         :: !(Maybe Text)
    , _jUndeclaredQueryParameters           :: !(Maybe [QueryParameter])
    , _jReferencedTables                    :: !(Maybe [TableReference])
    , _jStatementType                       :: !(Maybe Text)
    , _jReservationUsage                    :: !(Maybe [JobStatistics2ReservationUsageItem])
    , _jNumDmlAffectedRows                  :: !(Maybe (Textual Int64))
    , _jTimeline                            :: !(Maybe [QueryTimelineSample])
    , _jQueryPlan                           :: !(Maybe [ExplainQueryStage])
    , _jCacheHit                            :: !(Maybe Bool)
    , _jTotalBytesBilled                    :: !(Maybe (Textual Int64))
    , _jDdlOperationPerformed               :: !(Maybe Text)
    , _jTotalPartitionsProcessed            :: !(Maybe (Textual Int64))
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobStatistics2
    :: JobStatistics2
jobStatistics2 =
  JobStatistics2'
    { _jModelTrainingExpectedTotalIteration = Nothing
    , _jModelTraining = Nothing
    , _jTotalSlotMs = Nothing
    , _jDdlTargetRoutine = Nothing
    , _jDdlTargetTable = Nothing
    , _jEstimatedBytesProcessed = Nothing
    , _jModelTrainingCurrentIteration = Nothing
    , _jSchema = Nothing
    , _jTotalBytesProcessed = Nothing
    , _jBillingTier = Nothing
    , _jTotalBytesProcessedAccuracy = Nothing
    , _jUndeclaredQueryParameters = Nothing
    , _jReferencedTables = Nothing
    , _jStatementType = Nothing
    , _jReservationUsage = Nothing
    , _jNumDmlAffectedRows = Nothing
    , _jTimeline = Nothing
    , _jQueryPlan = Nothing
    , _jCacheHit = Nothing
    , _jTotalBytesBilled = Nothing
    , _jDdlOperationPerformed = Nothing
    , _jTotalPartitionsProcessed = Nothing
    }
jModelTrainingExpectedTotalIteration :: Lens' JobStatistics2 (Maybe Int64)
jModelTrainingExpectedTotalIteration
  = lens _jModelTrainingExpectedTotalIteration
      (\ s a ->
         s{_jModelTrainingExpectedTotalIteration = a})
      . mapping _Coerce
jModelTraining :: Lens' JobStatistics2 (Maybe BigQueryModelTraining)
jModelTraining
  = lens _jModelTraining
      (\ s a -> s{_jModelTraining = a})
jTotalSlotMs :: Lens' JobStatistics2 (Maybe Int64)
jTotalSlotMs
  = lens _jTotalSlotMs (\ s a -> s{_jTotalSlotMs = a})
      . mapping _Coerce
jDdlTargetRoutine :: Lens' JobStatistics2 (Maybe RoutineReference)
jDdlTargetRoutine
  = lens _jDdlTargetRoutine
      (\ s a -> s{_jDdlTargetRoutine = a})
jDdlTargetTable :: Lens' JobStatistics2 (Maybe TableReference)
jDdlTargetTable
  = lens _jDdlTargetTable
      (\ s a -> s{_jDdlTargetTable = a})
jEstimatedBytesProcessed :: Lens' JobStatistics2 (Maybe Int64)
jEstimatedBytesProcessed
  = lens _jEstimatedBytesProcessed
      (\ s a -> s{_jEstimatedBytesProcessed = a})
      . mapping _Coerce
jModelTrainingCurrentIteration :: Lens' JobStatistics2 (Maybe Int32)
jModelTrainingCurrentIteration
  = lens _jModelTrainingCurrentIteration
      (\ s a -> s{_jModelTrainingCurrentIteration = a})
      . mapping _Coerce
jSchema :: Lens' JobStatistics2 (Maybe TableSchema)
jSchema = lens _jSchema (\ s a -> s{_jSchema = a})
jTotalBytesProcessed :: Lens' JobStatistics2 (Maybe Int64)
jTotalBytesProcessed
  = lens _jTotalBytesProcessed
      (\ s a -> s{_jTotalBytesProcessed = a})
      . mapping _Coerce
jBillingTier :: Lens' JobStatistics2 (Maybe Int32)
jBillingTier
  = lens _jBillingTier (\ s a -> s{_jBillingTier = a})
      . mapping _Coerce
jTotalBytesProcessedAccuracy :: Lens' JobStatistics2 (Maybe Text)
jTotalBytesProcessedAccuracy
  = lens _jTotalBytesProcessedAccuracy
      (\ s a -> s{_jTotalBytesProcessedAccuracy = a})
jUndeclaredQueryParameters :: Lens' JobStatistics2 [QueryParameter]
jUndeclaredQueryParameters
  = lens _jUndeclaredQueryParameters
      (\ s a -> s{_jUndeclaredQueryParameters = a})
      . _Default
      . _Coerce
jReferencedTables :: Lens' JobStatistics2 [TableReference]
jReferencedTables
  = lens _jReferencedTables
      (\ s a -> s{_jReferencedTables = a})
      . _Default
      . _Coerce
jStatementType :: Lens' JobStatistics2 (Maybe Text)
jStatementType
  = lens _jStatementType
      (\ s a -> s{_jStatementType = a})
jReservationUsage :: Lens' JobStatistics2 [JobStatistics2ReservationUsageItem]
jReservationUsage
  = lens _jReservationUsage
      (\ s a -> s{_jReservationUsage = a})
      . _Default
      . _Coerce
jNumDmlAffectedRows :: Lens' JobStatistics2 (Maybe Int64)
jNumDmlAffectedRows
  = lens _jNumDmlAffectedRows
      (\ s a -> s{_jNumDmlAffectedRows = a})
      . mapping _Coerce
jTimeline :: Lens' JobStatistics2 [QueryTimelineSample]
jTimeline
  = lens _jTimeline (\ s a -> s{_jTimeline = a}) .
      _Default
      . _Coerce
jQueryPlan :: Lens' JobStatistics2 [ExplainQueryStage]
jQueryPlan
  = lens _jQueryPlan (\ s a -> s{_jQueryPlan = a}) .
      _Default
      . _Coerce
jCacheHit :: Lens' JobStatistics2 (Maybe Bool)
jCacheHit
  = lens _jCacheHit (\ s a -> s{_jCacheHit = a})
jTotalBytesBilled :: Lens' JobStatistics2 (Maybe Int64)
jTotalBytesBilled
  = lens _jTotalBytesBilled
      (\ s a -> s{_jTotalBytesBilled = a})
      . mapping _Coerce
jDdlOperationPerformed :: Lens' JobStatistics2 (Maybe Text)
jDdlOperationPerformed
  = lens _jDdlOperationPerformed
      (\ s a -> s{_jDdlOperationPerformed = a})
jTotalPartitionsProcessed :: Lens' JobStatistics2 (Maybe Int64)
jTotalPartitionsProcessed
  = lens _jTotalPartitionsProcessed
      (\ s a -> s{_jTotalPartitionsProcessed = a})
      . mapping _Coerce
instance FromJSON JobStatistics2 where
        parseJSON
          = withObject "JobStatistics2"
              (\ o ->
                 JobStatistics2' <$>
                   (o .:? "modelTrainingExpectedTotalIteration") <*>
                     (o .:? "modelTraining")
                     <*> (o .:? "totalSlotMs")
                     <*> (o .:? "ddlTargetRoutine")
                     <*> (o .:? "ddlTargetTable")
                     <*> (o .:? "estimatedBytesProcessed")
                     <*> (o .:? "modelTrainingCurrentIteration")
                     <*> (o .:? "schema")
                     <*> (o .:? "totalBytesProcessed")
                     <*> (o .:? "billingTier")
                     <*> (o .:? "totalBytesProcessedAccuracy")
                     <*> (o .:? "undeclaredQueryParameters" .!= mempty)
                     <*> (o .:? "referencedTables" .!= mempty)
                     <*> (o .:? "statementType")
                     <*> (o .:? "reservationUsage" .!= mempty)
                     <*> (o .:? "numDmlAffectedRows")
                     <*> (o .:? "timeline" .!= mempty)
                     <*> (o .:? "queryPlan" .!= mempty)
                     <*> (o .:? "cacheHit")
                     <*> (o .:? "totalBytesBilled")
                     <*> (o .:? "ddlOperationPerformed")
                     <*> (o .:? "totalPartitionsProcessed"))
instance ToJSON JobStatistics2 where
        toJSON JobStatistics2'{..}
          = object
              (catMaybes
                 [("modelTrainingExpectedTotalIteration" .=) <$>
                    _jModelTrainingExpectedTotalIteration,
                  ("modelTraining" .=) <$> _jModelTraining,
                  ("totalSlotMs" .=) <$> _jTotalSlotMs,
                  ("ddlTargetRoutine" .=) <$> _jDdlTargetRoutine,
                  ("ddlTargetTable" .=) <$> _jDdlTargetTable,
                  ("estimatedBytesProcessed" .=) <$>
                    _jEstimatedBytesProcessed,
                  ("modelTrainingCurrentIteration" .=) <$>
                    _jModelTrainingCurrentIteration,
                  ("schema" .=) <$> _jSchema,
                  ("totalBytesProcessed" .=) <$> _jTotalBytesProcessed,
                  ("billingTier" .=) <$> _jBillingTier,
                  ("totalBytesProcessedAccuracy" .=) <$>
                    _jTotalBytesProcessedAccuracy,
                  ("undeclaredQueryParameters" .=) <$>
                    _jUndeclaredQueryParameters,
                  ("referencedTables" .=) <$> _jReferencedTables,
                  ("statementType" .=) <$> _jStatementType,
                  ("reservationUsage" .=) <$> _jReservationUsage,
                  ("numDmlAffectedRows" .=) <$> _jNumDmlAffectedRows,
                  ("timeline" .=) <$> _jTimeline,
                  ("queryPlan" .=) <$> _jQueryPlan,
                  ("cacheHit" .=) <$> _jCacheHit,
                  ("totalBytesBilled" .=) <$> _jTotalBytesBilled,
                  ("ddlOperationPerformed" .=) <$>
                    _jDdlOperationPerformed,
                  ("totalPartitionsProcessed" .=) <$>
                    _jTotalPartitionsProcessed])
newtype TableFieldSchemaCategories =
  TableFieldSchemaCategories'
    { _tfscNames :: Maybe [Text]
    }
  deriving (Eq, Show, Data, Typeable, Generic)
tableFieldSchemaCategories
    :: TableFieldSchemaCategories
tableFieldSchemaCategories = TableFieldSchemaCategories' {_tfscNames = Nothing}
tfscNames :: Lens' TableFieldSchemaCategories [Text]
tfscNames
  = lens _tfscNames (\ s a -> s{_tfscNames = a}) .
      _Default
      . _Coerce
instance FromJSON TableFieldSchemaCategories where
        parseJSON
          = withObject "TableFieldSchemaCategories"
              (\ o ->
                 TableFieldSchemaCategories' <$>
                   (o .:? "names" .!= mempty))
instance ToJSON TableFieldSchemaCategories where
        toJSON TableFieldSchemaCategories'{..}
          = object (catMaybes [("names" .=) <$> _tfscNames])
data JobStatus =
  JobStatus'
    { _jsState       :: !(Maybe Text)
    , _jsErrorResult :: !(Maybe ErrorProto)
    , _jsErrors      :: !(Maybe [ErrorProto])
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobStatus
    :: JobStatus
jobStatus =
  JobStatus' {_jsState = Nothing, _jsErrorResult = Nothing, _jsErrors = Nothing}
jsState :: Lens' JobStatus (Maybe Text)
jsState = lens _jsState (\ s a -> s{_jsState = a})
jsErrorResult :: Lens' JobStatus (Maybe ErrorProto)
jsErrorResult
  = lens _jsErrorResult
      (\ s a -> s{_jsErrorResult = a})
jsErrors :: Lens' JobStatus [ErrorProto]
jsErrors
  = lens _jsErrors (\ s a -> s{_jsErrors = a}) .
      _Default
      . _Coerce
instance FromJSON JobStatus where
        parseJSON
          = withObject "JobStatus"
              (\ o ->
                 JobStatus' <$>
                   (o .:? "state") <*> (o .:? "errorResult") <*>
                     (o .:? "errors" .!= mempty))
instance ToJSON JobStatus where
        toJSON JobStatus'{..}
          = object
              (catMaybes
                 [("state" .=) <$> _jsState,
                  ("errorResult" .=) <$> _jsErrorResult,
                  ("errors" .=) <$> _jsErrors])
newtype TableLabels =
  TableLabels'
    { _tlAddtional :: HashMap Text Text
    }
  deriving (Eq, Show, Data, Typeable, Generic)
tableLabels
    :: HashMap Text Text 
    -> TableLabels
tableLabels pTlAddtional_ =
  TableLabels' {_tlAddtional = _Coerce # pTlAddtional_}
tlAddtional :: Lens' TableLabels (HashMap Text Text)
tlAddtional
  = lens _tlAddtional (\ s a -> s{_tlAddtional = a}) .
      _Coerce
instance FromJSON TableLabels where
        parseJSON
          = withObject "TableLabels"
              (\ o -> TableLabels' <$> (parseJSONObject o))
instance ToJSON TableLabels where
        toJSON = toJSON . _tlAddtional
data DestinationTableProperties =
  DestinationTableProperties'
    { _dtpFriendlyName :: !(Maybe Text)
    , _dtpLabels       :: !(Maybe DestinationTablePropertiesLabels)
    , _dtpDescription  :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
destinationTableProperties
    :: DestinationTableProperties
destinationTableProperties =
  DestinationTableProperties'
    { _dtpFriendlyName = Nothing
    , _dtpLabels = Nothing
    , _dtpDescription = Nothing
    }
dtpFriendlyName :: Lens' DestinationTableProperties (Maybe Text)
dtpFriendlyName
  = lens _dtpFriendlyName
      (\ s a -> s{_dtpFriendlyName = a})
dtpLabels :: Lens' DestinationTableProperties (Maybe DestinationTablePropertiesLabels)
dtpLabels
  = lens _dtpLabels (\ s a -> s{_dtpLabels = a})
dtpDescription :: Lens' DestinationTableProperties (Maybe Text)
dtpDescription
  = lens _dtpDescription
      (\ s a -> s{_dtpDescription = a})
instance FromJSON DestinationTableProperties where
        parseJSON
          = withObject "DestinationTableProperties"
              (\ o ->
                 DestinationTableProperties' <$>
                   (o .:? "friendlyName") <*> (o .:? "labels") <*>
                     (o .:? "description"))
instance ToJSON DestinationTableProperties where
        toJSON DestinationTableProperties'{..}
          = object
              (catMaybes
                 [("friendlyName" .=) <$> _dtpFriendlyName,
                  ("labels" .=) <$> _dtpLabels,
                  ("description" .=) <$> _dtpDescription])
data DataSetAccessItem =
  DataSetAccessItem'
    { _dsaiGroupByEmail :: !(Maybe Text)
    , _dsaiDomain       :: !(Maybe Text)
    , _dsaiSpecialGroup :: !(Maybe Text)
    , _dsaiRole         :: !(Maybe Text)
    , _dsaiIAMMember    :: !(Maybe Text)
    , _dsaiView         :: !(Maybe TableReference)
    , _dsaiUserByEmail  :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
dataSetAccessItem
    :: DataSetAccessItem
dataSetAccessItem =
  DataSetAccessItem'
    { _dsaiGroupByEmail = Nothing
    , _dsaiDomain = Nothing
    , _dsaiSpecialGroup = Nothing
    , _dsaiRole = Nothing
    , _dsaiIAMMember = Nothing
    , _dsaiView = Nothing
    , _dsaiUserByEmail = Nothing
    }
dsaiGroupByEmail :: Lens' DataSetAccessItem (Maybe Text)
dsaiGroupByEmail
  = lens _dsaiGroupByEmail
      (\ s a -> s{_dsaiGroupByEmail = a})
dsaiDomain :: Lens' DataSetAccessItem (Maybe Text)
dsaiDomain
  = lens _dsaiDomain (\ s a -> s{_dsaiDomain = a})
dsaiSpecialGroup :: Lens' DataSetAccessItem (Maybe Text)
dsaiSpecialGroup
  = lens _dsaiSpecialGroup
      (\ s a -> s{_dsaiSpecialGroup = a})
dsaiRole :: Lens' DataSetAccessItem (Maybe Text)
dsaiRole = lens _dsaiRole (\ s a -> s{_dsaiRole = a})
dsaiIAMMember :: Lens' DataSetAccessItem (Maybe Text)
dsaiIAMMember
  = lens _dsaiIAMMember
      (\ s a -> s{_dsaiIAMMember = a})
dsaiView :: Lens' DataSetAccessItem (Maybe TableReference)
dsaiView = lens _dsaiView (\ s a -> s{_dsaiView = a})
dsaiUserByEmail :: Lens' DataSetAccessItem (Maybe Text)
dsaiUserByEmail
  = lens _dsaiUserByEmail
      (\ s a -> s{_dsaiUserByEmail = a})
instance FromJSON DataSetAccessItem where
        parseJSON
          = withObject "DataSetAccessItem"
              (\ o ->
                 DataSetAccessItem' <$>
                   (o .:? "groupByEmail") <*> (o .:? "domain") <*>
                     (o .:? "specialGroup")
                     <*> (o .:? "role")
                     <*> (o .:? "iamMember")
                     <*> (o .:? "view")
                     <*> (o .:? "userByEmail"))
instance ToJSON DataSetAccessItem where
        toJSON DataSetAccessItem'{..}
          = object
              (catMaybes
                 [("groupByEmail" .=) <$> _dsaiGroupByEmail,
                  ("domain" .=) <$> _dsaiDomain,
                  ("specialGroup" .=) <$> _dsaiSpecialGroup,
                  ("role" .=) <$> _dsaiRole,
                  ("iamMember" .=) <$> _dsaiIAMMember,
                  ("view" .=) <$> _dsaiView,
                  ("userByEmail" .=) <$> _dsaiUserByEmail])
data BqmlTrainingRun =
  BqmlTrainingRun'
    { _btrState            :: !(Maybe Text)
    , _btrStartTime        :: !(Maybe DateTime')
    , _btrIterationResults :: !(Maybe [BqmlIterationResult])
    , _btrTrainingOptions  :: !(Maybe BqmlTrainingRunTrainingOptions)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
bqmlTrainingRun
    :: BqmlTrainingRun
bqmlTrainingRun =
  BqmlTrainingRun'
    { _btrState = Nothing
    , _btrStartTime = Nothing
    , _btrIterationResults = Nothing
    , _btrTrainingOptions = Nothing
    }
btrState :: Lens' BqmlTrainingRun (Maybe Text)
btrState = lens _btrState (\ s a -> s{_btrState = a})
btrStartTime :: Lens' BqmlTrainingRun (Maybe UTCTime)
btrStartTime
  = lens _btrStartTime (\ s a -> s{_btrStartTime = a})
      . mapping _DateTime
btrIterationResults :: Lens' BqmlTrainingRun [BqmlIterationResult]
btrIterationResults
  = lens _btrIterationResults
      (\ s a -> s{_btrIterationResults = a})
      . _Default
      . _Coerce
btrTrainingOptions :: Lens' BqmlTrainingRun (Maybe BqmlTrainingRunTrainingOptions)
btrTrainingOptions
  = lens _btrTrainingOptions
      (\ s a -> s{_btrTrainingOptions = a})
instance FromJSON BqmlTrainingRun where
        parseJSON
          = withObject "BqmlTrainingRun"
              (\ o ->
                 BqmlTrainingRun' <$>
                   (o .:? "state") <*> (o .:? "startTime") <*>
                     (o .:? "iterationResults" .!= mempty)
                     <*> (o .:? "trainingOptions"))
instance ToJSON BqmlTrainingRun where
        toJSON BqmlTrainingRun'{..}
          = object
              (catMaybes
                 [("state" .=) <$> _btrState,
                  ("startTime" .=) <$> _btrStartTime,
                  ("iterationResults" .=) <$> _btrIterationResults,
                  ("trainingOptions" .=) <$> _btrTrainingOptions])
data TableDataInsertAllResponse =
  TableDataInsertAllResponse'
    { _tKind         :: !Text
    , _tInsertErrors :: !(Maybe [TableDataInsertAllResponseInsertErrorsItem])
    }
  deriving (Eq, Show, Data, Typeable, Generic)
tableDataInsertAllResponse
    :: TableDataInsertAllResponse
tableDataInsertAllResponse =
  TableDataInsertAllResponse'
    {_tKind = "bigquery#tableDataInsertAllResponse", _tInsertErrors = Nothing}
tKind :: Lens' TableDataInsertAllResponse Text
tKind = lens _tKind (\ s a -> s{_tKind = a})
tInsertErrors :: Lens' TableDataInsertAllResponse [TableDataInsertAllResponseInsertErrorsItem]
tInsertErrors
  = lens _tInsertErrors
      (\ s a -> s{_tInsertErrors = a})
      . _Default
      . _Coerce
instance FromJSON TableDataInsertAllResponse where
        parseJSON
          = withObject "TableDataInsertAllResponse"
              (\ o ->
                 TableDataInsertAllResponse' <$>
                   (o .:? "kind" .!=
                      "bigquery#tableDataInsertAllResponse")
                     <*> (o .:? "insertErrors" .!= mempty))
instance ToJSON TableDataInsertAllResponse where
        toJSON TableDataInsertAllResponse'{..}
          = object
              (catMaybes
                 [Just ("kind" .= _tKind),
                  ("insertErrors" .=) <$> _tInsertErrors])
data QueryParameterType =
  QueryParameterType'
    { _qptStructTypes :: !(Maybe [QueryParameterTypeStructTypesItem])
    , _qptType        :: !(Maybe Text)
    , _qptArrayType   :: !(Maybe QueryParameterType)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
queryParameterType
    :: QueryParameterType
queryParameterType =
  QueryParameterType'
    {_qptStructTypes = Nothing, _qptType = Nothing, _qptArrayType = Nothing}
qptStructTypes :: Lens' QueryParameterType [QueryParameterTypeStructTypesItem]
qptStructTypes
  = lens _qptStructTypes
      (\ s a -> s{_qptStructTypes = a})
      . _Default
      . _Coerce
qptType :: Lens' QueryParameterType (Maybe Text)
qptType = lens _qptType (\ s a -> s{_qptType = a})
qptArrayType :: Lens' QueryParameterType (Maybe QueryParameterType)
qptArrayType
  = lens _qptArrayType (\ s a -> s{_qptArrayType = a})
instance FromJSON QueryParameterType where
        parseJSON
          = withObject "QueryParameterType"
              (\ o ->
                 QueryParameterType' <$>
                   (o .:? "structTypes" .!= mempty) <*> (o .:? "type")
                     <*> (o .:? "arrayType"))
instance ToJSON QueryParameterType where
        toJSON QueryParameterType'{..}
          = object
              (catMaybes
                 [("structTypes" .=) <$> _qptStructTypes,
                  ("type" .=) <$> _qptType,
                  ("arrayType" .=) <$> _qptArrayType])
data Table =
  Table'
    { _tabMaterializedView          :: !(Maybe MaterializedViewDefinition)
    , _tabCreationTime              :: !(Maybe (Textual Int64))
    , _tabEtag                      :: !(Maybe Text)
    , _tabNumBytes                  :: !(Maybe (Textual Int64))
    , _tabClustering                :: !(Maybe Clustering)
    , _tabExternalDataConfiguration :: !(Maybe ExternalDataConfiguration)
    , _tabRangePartitioning         :: !(Maybe RangePartitioning)
    , _tabLocation                  :: !(Maybe Text)
    , _tabTableReference            :: !(Maybe TableReference)
    , _tabFriendlyName              :: !(Maybe Text)
    , _tabKind                      :: !Text
    , _tabLastModifiedTime          :: !(Maybe (Textual Word64))
    , _tabSchema                    :: !(Maybe TableSchema)
    , _tabStreamingBuffer           :: !(Maybe Streamingbuffer)
    , _tabSelfLink                  :: !(Maybe Text)
    , _tabRequirePartitionFilter    :: !(Maybe Bool)
    , _tabEncryptionConfiguration   :: !(Maybe EncryptionConfiguration)
    , _tabModel                     :: !(Maybe ModelDefinition)
    , _tabTimePartitioning          :: !(Maybe TimePartitioning)
    , _tabNumRows                   :: !(Maybe (Textual Word64))
    , _tabNumPhysicalBytes          :: !(Maybe (Textual Int64))
    , _tabView                      :: !(Maybe ViewDefinition)
    , _tabId                        :: !(Maybe Text)
    , _tabLabels                    :: !(Maybe TableLabels)
    , _tabType                      :: !(Maybe Text)
    , _tabNumLongTermBytes          :: !(Maybe (Textual Int64))
    , _tabExpirationTime            :: !(Maybe (Textual Int64))
    , _tabDescription               :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
table
    :: Table
table =
  Table'
    { _tabMaterializedView = Nothing
    , _tabCreationTime = Nothing
    , _tabEtag = Nothing
    , _tabNumBytes = Nothing
    , _tabClustering = Nothing
    , _tabExternalDataConfiguration = Nothing
    , _tabRangePartitioning = Nothing
    , _tabLocation = Nothing
    , _tabTableReference = Nothing
    , _tabFriendlyName = Nothing
    , _tabKind = "bigquery#table"
    , _tabLastModifiedTime = Nothing
    , _tabSchema = Nothing
    , _tabStreamingBuffer = Nothing
    , _tabSelfLink = Nothing
    , _tabRequirePartitionFilter = Nothing
    , _tabEncryptionConfiguration = Nothing
    , _tabModel = Nothing
    , _tabTimePartitioning = Nothing
    , _tabNumRows = Nothing
    , _tabNumPhysicalBytes = Nothing
    , _tabView = Nothing
    , _tabId = Nothing
    , _tabLabels = Nothing
    , _tabType = Nothing
    , _tabNumLongTermBytes = Nothing
    , _tabExpirationTime = Nothing
    , _tabDescription = Nothing
    }
tabMaterializedView :: Lens' Table (Maybe MaterializedViewDefinition)
tabMaterializedView
  = lens _tabMaterializedView
      (\ s a -> s{_tabMaterializedView = a})
tabCreationTime :: Lens' Table (Maybe Int64)
tabCreationTime
  = lens _tabCreationTime
      (\ s a -> s{_tabCreationTime = a})
      . mapping _Coerce
tabEtag :: Lens' Table (Maybe Text)
tabEtag = lens _tabEtag (\ s a -> s{_tabEtag = a})
tabNumBytes :: Lens' Table (Maybe Int64)
tabNumBytes
  = lens _tabNumBytes (\ s a -> s{_tabNumBytes = a}) .
      mapping _Coerce
tabClustering :: Lens' Table (Maybe Clustering)
tabClustering
  = lens _tabClustering
      (\ s a -> s{_tabClustering = a})
tabExternalDataConfiguration :: Lens' Table (Maybe ExternalDataConfiguration)
tabExternalDataConfiguration
  = lens _tabExternalDataConfiguration
      (\ s a -> s{_tabExternalDataConfiguration = a})
tabRangePartitioning :: Lens' Table (Maybe RangePartitioning)
tabRangePartitioning
  = lens _tabRangePartitioning
      (\ s a -> s{_tabRangePartitioning = a})
tabLocation :: Lens' Table (Maybe Text)
tabLocation
  = lens _tabLocation (\ s a -> s{_tabLocation = a})
tabTableReference :: Lens' Table (Maybe TableReference)
tabTableReference
  = lens _tabTableReference
      (\ s a -> s{_tabTableReference = a})
tabFriendlyName :: Lens' Table (Maybe Text)
tabFriendlyName
  = lens _tabFriendlyName
      (\ s a -> s{_tabFriendlyName = a})
tabKind :: Lens' Table Text
tabKind = lens _tabKind (\ s a -> s{_tabKind = a})
tabLastModifiedTime :: Lens' Table (Maybe Word64)
tabLastModifiedTime
  = lens _tabLastModifiedTime
      (\ s a -> s{_tabLastModifiedTime = a})
      . mapping _Coerce
tabSchema :: Lens' Table (Maybe TableSchema)
tabSchema
  = lens _tabSchema (\ s a -> s{_tabSchema = a})
tabStreamingBuffer :: Lens' Table (Maybe Streamingbuffer)
tabStreamingBuffer
  = lens _tabStreamingBuffer
      (\ s a -> s{_tabStreamingBuffer = a})
tabSelfLink :: Lens' Table (Maybe Text)
tabSelfLink
  = lens _tabSelfLink (\ s a -> s{_tabSelfLink = a})
tabRequirePartitionFilter :: Lens' Table (Maybe Bool)
tabRequirePartitionFilter
  = lens _tabRequirePartitionFilter
      (\ s a -> s{_tabRequirePartitionFilter = a})
tabEncryptionConfiguration :: Lens' Table (Maybe EncryptionConfiguration)
tabEncryptionConfiguration
  = lens _tabEncryptionConfiguration
      (\ s a -> s{_tabEncryptionConfiguration = a})
tabModel :: Lens' Table (Maybe ModelDefinition)
tabModel = lens _tabModel (\ s a -> s{_tabModel = a})
tabTimePartitioning :: Lens' Table (Maybe TimePartitioning)
tabTimePartitioning
  = lens _tabTimePartitioning
      (\ s a -> s{_tabTimePartitioning = a})
tabNumRows :: Lens' Table (Maybe Word64)
tabNumRows
  = lens _tabNumRows (\ s a -> s{_tabNumRows = a}) .
      mapping _Coerce
tabNumPhysicalBytes :: Lens' Table (Maybe Int64)
tabNumPhysicalBytes
  = lens _tabNumPhysicalBytes
      (\ s a -> s{_tabNumPhysicalBytes = a})
      . mapping _Coerce
tabView :: Lens' Table (Maybe ViewDefinition)
tabView = lens _tabView (\ s a -> s{_tabView = a})
tabId :: Lens' Table (Maybe Text)
tabId = lens _tabId (\ s a -> s{_tabId = a})
tabLabels :: Lens' Table (Maybe TableLabels)
tabLabels
  = lens _tabLabels (\ s a -> s{_tabLabels = a})
tabType :: Lens' Table (Maybe Text)
tabType = lens _tabType (\ s a -> s{_tabType = a})
tabNumLongTermBytes :: Lens' Table (Maybe Int64)
tabNumLongTermBytes
  = lens _tabNumLongTermBytes
      (\ s a -> s{_tabNumLongTermBytes = a})
      . mapping _Coerce
tabExpirationTime :: Lens' Table (Maybe Int64)
tabExpirationTime
  = lens _tabExpirationTime
      (\ s a -> s{_tabExpirationTime = a})
      . mapping _Coerce
tabDescription :: Lens' Table (Maybe Text)
tabDescription
  = lens _tabDescription
      (\ s a -> s{_tabDescription = a})
instance FromJSON Table where
        parseJSON
          = withObject "Table"
              (\ o ->
                 Table' <$>
                   (o .:? "materializedView") <*> (o .:? "creationTime")
                     <*> (o .:? "etag")
                     <*> (o .:? "numBytes")
                     <*> (o .:? "clustering")
                     <*> (o .:? "externalDataConfiguration")
                     <*> (o .:? "rangePartitioning")
                     <*> (o .:? "location")
                     <*> (o .:? "tableReference")
                     <*> (o .:? "friendlyName")
                     <*> (o .:? "kind" .!= "bigquery#table")
                     <*> (o .:? "lastModifiedTime")
                     <*> (o .:? "schema")
                     <*> (o .:? "streamingBuffer")
                     <*> (o .:? "selfLink")
                     <*> (o .:? "requirePartitionFilter")
                     <*> (o .:? "encryptionConfiguration")
                     <*> (o .:? "model")
                     <*> (o .:? "timePartitioning")
                     <*> (o .:? "numRows")
                     <*> (o .:? "numPhysicalBytes")
                     <*> (o .:? "view")
                     <*> (o .:? "id")
                     <*> (o .:? "labels")
                     <*> (o .:? "type")
                     <*> (o .:? "numLongTermBytes")
                     <*> (o .:? "expirationTime")
                     <*> (o .:? "description"))
instance ToJSON Table where
        toJSON Table'{..}
          = object
              (catMaybes
                 [("materializedView" .=) <$> _tabMaterializedView,
                  ("creationTime" .=) <$> _tabCreationTime,
                  ("etag" .=) <$> _tabEtag,
                  ("numBytes" .=) <$> _tabNumBytes,
                  ("clustering" .=) <$> _tabClustering,
                  ("externalDataConfiguration" .=) <$>
                    _tabExternalDataConfiguration,
                  ("rangePartitioning" .=) <$> _tabRangePartitioning,
                  ("location" .=) <$> _tabLocation,
                  ("tableReference" .=) <$> _tabTableReference,
                  ("friendlyName" .=) <$> _tabFriendlyName,
                  Just ("kind" .= _tabKind),
                  ("lastModifiedTime" .=) <$> _tabLastModifiedTime,
                  ("schema" .=) <$> _tabSchema,
                  ("streamingBuffer" .=) <$> _tabStreamingBuffer,
                  ("selfLink" .=) <$> _tabSelfLink,
                  ("requirePartitionFilter" .=) <$>
                    _tabRequirePartitionFilter,
                  ("encryptionConfiguration" .=) <$>
                    _tabEncryptionConfiguration,
                  ("model" .=) <$> _tabModel,
                  ("timePartitioning" .=) <$> _tabTimePartitioning,
                  ("numRows" .=) <$> _tabNumRows,
                  ("numPhysicalBytes" .=) <$> _tabNumPhysicalBytes,
                  ("view" .=) <$> _tabView, ("id" .=) <$> _tabId,
                  ("labels" .=) <$> _tabLabels,
                  ("type" .=) <$> _tabType,
                  ("numLongTermBytes" .=) <$> _tabNumLongTermBytes,
                  ("expirationTime" .=) <$> _tabExpirationTime,
                  ("description" .=) <$> _tabDescription])
data ErrorProto =
  ErrorProto'
    { _epDebugInfo :: !(Maybe Text)
    , _epLocation  :: !(Maybe Text)
    , _epReason    :: !(Maybe Text)
    , _epMessage   :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
errorProto
    :: ErrorProto
errorProto =
  ErrorProto'
    { _epDebugInfo = Nothing
    , _epLocation = Nothing
    , _epReason = Nothing
    , _epMessage = Nothing
    }
epDebugInfo :: Lens' ErrorProto (Maybe Text)
epDebugInfo
  = lens _epDebugInfo (\ s a -> s{_epDebugInfo = a})
epLocation :: Lens' ErrorProto (Maybe Text)
epLocation
  = lens _epLocation (\ s a -> s{_epLocation = a})
epReason :: Lens' ErrorProto (Maybe Text)
epReason = lens _epReason (\ s a -> s{_epReason = a})
epMessage :: Lens' ErrorProto (Maybe Text)
epMessage
  = lens _epMessage (\ s a -> s{_epMessage = a})
instance FromJSON ErrorProto where
        parseJSON
          = withObject "ErrorProto"
              (\ o ->
                 ErrorProto' <$>
                   (o .:? "debugInfo") <*> (o .:? "location") <*>
                     (o .:? "reason")
                     <*> (o .:? "message"))
instance ToJSON ErrorProto where
        toJSON ErrorProto'{..}
          = object
              (catMaybes
                 [("debugInfo" .=) <$> _epDebugInfo,
                  ("location" .=) <$> _epLocation,
                  ("reason" .=) <$> _epReason,
                  ("message" .=) <$> _epMessage])
data CSVOptions =
  CSVOptions'
    { _coSkipLeadingRows     :: !(Maybe (Textual Int64))
    , _coAllowJaggedRows     :: !(Maybe Bool)
    , _coAllowQuotedNewlines :: !(Maybe Bool)
    , _coQuote               :: !Text
    , _coEncoding            :: !(Maybe Text)
    , _coFieldDelimiter      :: !(Maybe Text)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
csvOptions
    :: CSVOptions
csvOptions =
  CSVOptions'
    { _coSkipLeadingRows = Nothing
    , _coAllowJaggedRows = Nothing
    , _coAllowQuotedNewlines = Nothing
    , _coQuote = "\""
    , _coEncoding = Nothing
    , _coFieldDelimiter = Nothing
    }
coSkipLeadingRows :: Lens' CSVOptions (Maybe Int64)
coSkipLeadingRows
  = lens _coSkipLeadingRows
      (\ s a -> s{_coSkipLeadingRows = a})
      . mapping _Coerce
coAllowJaggedRows :: Lens' CSVOptions (Maybe Bool)
coAllowJaggedRows
  = lens _coAllowJaggedRows
      (\ s a -> s{_coAllowJaggedRows = a})
coAllowQuotedNewlines :: Lens' CSVOptions (Maybe Bool)
coAllowQuotedNewlines
  = lens _coAllowQuotedNewlines
      (\ s a -> s{_coAllowQuotedNewlines = a})
coQuote :: Lens' CSVOptions Text
coQuote = lens _coQuote (\ s a -> s{_coQuote = a})
coEncoding :: Lens' CSVOptions (Maybe Text)
coEncoding
  = lens _coEncoding (\ s a -> s{_coEncoding = a})
coFieldDelimiter :: Lens' CSVOptions (Maybe Text)
coFieldDelimiter
  = lens _coFieldDelimiter
      (\ s a -> s{_coFieldDelimiter = a})
instance FromJSON CSVOptions where
        parseJSON
          = withObject "CSVOptions"
              (\ o ->
                 CSVOptions' <$>
                   (o .:? "skipLeadingRows") <*>
                     (o .:? "allowJaggedRows")
                     <*> (o .:? "allowQuotedNewlines")
                     <*> (o .:? "quote" .!= "\"")
                     <*> (o .:? "encoding")
                     <*> (o .:? "fieldDelimiter"))
instance ToJSON CSVOptions where
        toJSON CSVOptions'{..}
          = object
              (catMaybes
                 [("skipLeadingRows" .=) <$> _coSkipLeadingRows,
                  ("allowJaggedRows" .=) <$> _coAllowJaggedRows,
                  ("allowQuotedNewlines" .=) <$>
                    _coAllowQuotedNewlines,
                  Just ("quote" .= _coQuote),
                  ("encoding" .=) <$> _coEncoding,
                  ("fieldDelimiter" .=) <$> _coFieldDelimiter])
newtype DestinationTablePropertiesLabels =
  DestinationTablePropertiesLabels'
    { _dtplAddtional :: HashMap Text Text
    }
  deriving (Eq, Show, Data, Typeable, Generic)
destinationTablePropertiesLabels
    :: HashMap Text Text 
    -> DestinationTablePropertiesLabels
destinationTablePropertiesLabels pDtplAddtional_ =
  DestinationTablePropertiesLabels' {_dtplAddtional = _Coerce # pDtplAddtional_}
dtplAddtional :: Lens' DestinationTablePropertiesLabels (HashMap Text Text)
dtplAddtional
  = lens _dtplAddtional
      (\ s a -> s{_dtplAddtional = a})
      . _Coerce
instance FromJSON DestinationTablePropertiesLabels
         where
        parseJSON
          = withObject "DestinationTablePropertiesLabels"
              (\ o ->
                 DestinationTablePropertiesLabels' <$>
                   (parseJSONObject o))
instance ToJSON DestinationTablePropertiesLabels
         where
        toJSON = toJSON . _dtplAddtional
data JobStatistics3 =
  JobStatistics3'
    { _jsInputFiles     :: !(Maybe (Textual Int64))
    , _jsOutputRows     :: !(Maybe (Textual Int64))
    , _jsOutputBytes    :: !(Maybe (Textual Int64))
    , _jsInputFileBytes :: !(Maybe (Textual Int64))
    , _jsBadRecords     :: !(Maybe (Textual Int64))
    }
  deriving (Eq, Show, Data, Typeable, Generic)
jobStatistics3
    :: JobStatistics3
jobStatistics3 =
  JobStatistics3'
    { _jsInputFiles = Nothing
    , _jsOutputRows = Nothing
    , _jsOutputBytes = Nothing
    , _jsInputFileBytes = Nothing
    , _jsBadRecords = Nothing
    }
jsInputFiles :: Lens' JobStatistics3 (Maybe Int64)
jsInputFiles
  = lens _jsInputFiles (\ s a -> s{_jsInputFiles = a})
      . mapping _Coerce
jsOutputRows :: Lens' JobStatistics3 (Maybe Int64)
jsOutputRows
  = lens _jsOutputRows (\ s a -> s{_jsOutputRows = a})
      . mapping _Coerce
jsOutputBytes :: Lens' JobStatistics3 (Maybe Int64)
jsOutputBytes
  = lens _jsOutputBytes
      (\ s a -> s{_jsOutputBytes = a})
      . mapping _Coerce
jsInputFileBytes :: Lens' JobStatistics3 (Maybe Int64)
jsInputFileBytes
  = lens _jsInputFileBytes
      (\ s a -> s{_jsInputFileBytes = a})
      . mapping _Coerce
jsBadRecords :: Lens' JobStatistics3 (Maybe Int64)
jsBadRecords
  = lens _jsBadRecords (\ s a -> s{_jsBadRecords = a})
      . mapping _Coerce
instance FromJSON JobStatistics3 where
        parseJSON
          = withObject "JobStatistics3"
              (\ o ->
                 JobStatistics3' <$>
                   (o .:? "inputFiles") <*> (o .:? "outputRows") <*>
                     (o .:? "outputBytes")
                     <*> (o .:? "inputFileBytes")
                     <*> (o .:? "badRecords"))
instance ToJSON JobStatistics3 where
        toJSON JobStatistics3'{..}
          = object
              (catMaybes
                 [("inputFiles" .=) <$> _jsInputFiles,
                  ("outputRows" .=) <$> _jsOutputRows,
                  ("outputBytes" .=) <$> _jsOutputBytes,
                  ("inputFileBytes" .=) <$> _jsInputFileBytes,
                  ("badRecords" .=) <$> _jsBadRecords])
data QueryResponse =
  QueryResponse'
    { _qJobReference        :: !(Maybe JobReference)
    , _qKind                :: !Text
    , _qSchema              :: !(Maybe TableSchema)
    , _qTotalBytesProcessed :: !(Maybe (Textual Int64))
    , _qRows                :: !(Maybe [TableRow])
    , _qPageToken           :: !(Maybe Text)
    , _qNumDmlAffectedRows  :: !(Maybe (Textual Int64))
    , _qTotalRows           :: !(Maybe (Textual Word64))
    , _qErrors              :: !(Maybe [ErrorProto])
    , _qJobComplete         :: !(Maybe Bool)
    , _qCacheHit            :: !(Maybe Bool)
    }
  deriving (Eq, Show, Data, Typeable, Generic)
queryResponse
    :: QueryResponse
queryResponse =
  QueryResponse'
    { _qJobReference = Nothing
    , _qKind = "bigquery#queryResponse"
    , _qSchema = Nothing
    , _qTotalBytesProcessed = Nothing
    , _qRows = Nothing
    , _qPageToken = Nothing
    , _qNumDmlAffectedRows = Nothing
    , _qTotalRows = Nothing
    , _qErrors = Nothing
    , _qJobComplete = Nothing
    , _qCacheHit = Nothing
    }
qJobReference :: Lens' QueryResponse (Maybe JobReference)
qJobReference
  = lens _qJobReference
      (\ s a -> s{_qJobReference = a})
qKind :: Lens' QueryResponse Text
qKind = lens _qKind (\ s a -> s{_qKind = a})
qSchema :: Lens' QueryResponse (Maybe TableSchema)
qSchema = lens _qSchema (\ s a -> s{_qSchema = a})
qTotalBytesProcessed :: Lens' QueryResponse (Maybe Int64)
qTotalBytesProcessed
  = lens _qTotalBytesProcessed
      (\ s a -> s{_qTotalBytesProcessed = a})
      . mapping _Coerce
qRows :: Lens' QueryResponse [TableRow]
qRows
  = lens _qRows (\ s a -> s{_qRows = a}) . _Default .
      _Coerce
qPageToken :: Lens' QueryResponse (Maybe Text)
qPageToken
  = lens _qPageToken (\ s a -> s{_qPageToken = a})
qNumDmlAffectedRows :: Lens' QueryResponse (Maybe Int64)
qNumDmlAffectedRows
  = lens _qNumDmlAffectedRows
      (\ s a -> s{_qNumDmlAffectedRows = a})
      . mapping _Coerce
qTotalRows :: Lens' QueryResponse (Maybe Word64)
qTotalRows
  = lens _qTotalRows (\ s a -> s{_qTotalRows = a}) .
      mapping _Coerce
qErrors :: Lens' QueryResponse [ErrorProto]
qErrors
  = lens _qErrors (\ s a -> s{_qErrors = a}) . _Default
      . _Coerce
qJobComplete :: Lens' QueryResponse (Maybe Bool)
qJobComplete
  = lens _qJobComplete (\ s a -> s{_qJobComplete = a})
qCacheHit :: Lens' QueryResponse (Maybe Bool)
qCacheHit
  = lens _qCacheHit (\ s a -> s{_qCacheHit = a})
instance FromJSON QueryResponse where
        parseJSON
          = withObject "QueryResponse"
              (\ o ->
                 QueryResponse' <$>
                   (o .:? "jobReference") <*>
                     (o .:? "kind" .!= "bigquery#queryResponse")
                     <*> (o .:? "schema")
                     <*> (o .:? "totalBytesProcessed")
                     <*> (o .:? "rows" .!= mempty)
                     <*> (o .:? "pageToken")
                     <*> (o .:? "numDmlAffectedRows")
                     <*> (o .:? "totalRows")
                     <*> (o .:? "errors" .!= mempty)
                     <*> (o .:? "jobComplete")
                     <*> (o .:? "cacheHit"))
instance ToJSON QueryResponse where
        toJSON QueryResponse'{..}
          = object
              (catMaybes
                 [("jobReference" .=) <$> _qJobReference,
                  Just ("kind" .= _qKind), ("schema" .=) <$> _qSchema,
                  ("totalBytesProcessed" .=) <$> _qTotalBytesProcessed,
                  ("rows" .=) <$> _qRows,
                  ("pageToken" .=) <$> _qPageToken,
                  ("numDmlAffectedRows" .=) <$> _qNumDmlAffectedRows,
                  ("totalRows" .=) <$> _qTotalRows,
                  ("errors" .=) <$> _qErrors,
                  ("jobComplete" .=) <$> _qJobComplete,
                  ("cacheHit" .=) <$> _qCacheHit])
newtype DataSetListDataSetsItemLabels =
  DataSetListDataSetsItemLabels'
    { _dsldsilAddtional :: HashMap Text Text
    }
  deriving (Eq, Show, Data, Typeable, Generic)
dataSetListDataSetsItemLabels
    :: HashMap Text Text 
    -> DataSetListDataSetsItemLabels
dataSetListDataSetsItemLabels pDsldsilAddtional_ =
  DataSetListDataSetsItemLabels'
    {_dsldsilAddtional = _Coerce # pDsldsilAddtional_}
dsldsilAddtional :: Lens' DataSetListDataSetsItemLabels (HashMap Text Text)
dsldsilAddtional
  = lens _dsldsilAddtional
      (\ s a -> s{_dsldsilAddtional = a})
      . _Coerce
instance FromJSON DataSetListDataSetsItemLabels where
        parseJSON
          = withObject "DataSetListDataSetsItemLabels"
              (\ o ->
                 DataSetListDataSetsItemLabels' <$>
                   (parseJSONObject o))
instance ToJSON DataSetListDataSetsItemLabels where
        toJSON = toJSON . _dsldsilAddtional
newtype TableListTablesItemView =
  TableListTablesItemView'
    { _tltivUseLegacySQL :: Maybe Bool
    }
  deriving (Eq, Show, Data, Typeable, Generic)
tableListTablesItemView
    :: TableListTablesItemView
tableListTablesItemView =
  TableListTablesItemView' {_tltivUseLegacySQL = Nothing}
tltivUseLegacySQL :: Lens' TableListTablesItemView (Maybe Bool)
tltivUseLegacySQL
  = lens _tltivUseLegacySQL
      (\ s a -> s{_tltivUseLegacySQL = a})
instance FromJSON TableListTablesItemView where
        parseJSON
          = withObject "TableListTablesItemView"
              (\ o ->
                 TableListTablesItemView' <$> (o .:? "useLegacySql"))
instance ToJSON TableListTablesItemView where
        toJSON TableListTablesItemView'{..}
          = object
              (catMaybes
                 [("useLegacySql" .=) <$> _tltivUseLegacySQL])
newtype TableListTablesItemLabels =
  TableListTablesItemLabels'
    { _tltilAddtional :: HashMap Text Text
    }
  deriving (Eq, Show, Data, Typeable, Generic)
tableListTablesItemLabels
    :: HashMap Text Text 
    -> TableListTablesItemLabels
tableListTablesItemLabels pTltilAddtional_ =
  TableListTablesItemLabels' {_tltilAddtional = _Coerce # pTltilAddtional_}
tltilAddtional :: Lens' TableListTablesItemLabels (HashMap Text Text)
tltilAddtional
  = lens _tltilAddtional
      (\ s a -> s{_tltilAddtional = a})
      . _Coerce
instance FromJSON TableListTablesItemLabels where
        parseJSON
          = withObject "TableListTablesItemLabels"
              (\ o ->
                 TableListTablesItemLabels' <$> (parseJSONObject o))
instance ToJSON TableListTablesItemLabels where
        toJSON = toJSON . _tltilAddtional