module Network.Google.AppEngine.Types.Product where
import Network.Google.AppEngine.Types.Sum
import Network.Google.Prelude
data Status = Status
{ _sDetails :: !(Maybe [StatusDetailsItem])
, _sCode :: !(Maybe (Textual Int32))
, _sMessage :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
status
:: Status
status =
Status
{ _sDetails = Nothing
, _sCode = Nothing
, _sMessage = Nothing
}
sDetails :: Lens' Status [StatusDetailsItem]
sDetails
= lens _sDetails (\ s a -> s{_sDetails = a}) .
_Default
. _Coerce
sCode :: Lens' Status (Maybe Int32)
sCode
= lens _sCode (\ s a -> s{_sCode = a}) .
mapping _Coerce
sMessage :: Lens' Status (Maybe Text)
sMessage = lens _sMessage (\ s a -> s{_sMessage = a})
instance FromJSON Status where
parseJSON
= withObject "Status"
(\ o ->
Status <$>
(o .:? "details" .!= mempty) <*> (o .:? "code") <*>
(o .:? "message"))
instance ToJSON Status where
toJSON Status{..}
= object
(catMaybes
[("details" .=) <$> _sDetails,
("code" .=) <$> _sCode,
("message" .=) <$> _sMessage])
newtype OperationSchema = OperationSchema
{ _osAddtional :: HashMap Text JSONValue
} deriving (Eq,Show,Data,Typeable,Generic)
operationSchema
:: HashMap Text JSONValue
-> OperationSchema
operationSchema pOsAddtional_ =
OperationSchema
{ _osAddtional = _Coerce # pOsAddtional_
}
osAddtional :: Lens' OperationSchema (HashMap Text JSONValue)
osAddtional
= lens _osAddtional (\ s a -> s{_osAddtional = a}) .
_Coerce
instance FromJSON OperationSchema where
parseJSON
= withObject "OperationSchema"
(\ o -> OperationSchema <$> (parseJSONObject o))
instance ToJSON OperationSchema where
toJSON = toJSON . _osAddtional
data TrafficSplit = TrafficSplit
{ _tsShardBy :: !(Maybe Text)
, _tsAllocations :: !(Maybe TrafficSplitAllocations)
} deriving (Eq,Show,Data,Typeable,Generic)
trafficSplit
:: TrafficSplit
trafficSplit =
TrafficSplit
{ _tsShardBy = Nothing
, _tsAllocations = Nothing
}
tsShardBy :: Lens' TrafficSplit (Maybe Text)
tsShardBy
= lens _tsShardBy (\ s a -> s{_tsShardBy = a})
tsAllocations :: Lens' TrafficSplit (Maybe TrafficSplitAllocations)
tsAllocations
= lens _tsAllocations
(\ s a -> s{_tsAllocations = a})
instance FromJSON TrafficSplit where
parseJSON
= withObject "TrafficSplit"
(\ o ->
TrafficSplit <$>
(o .:? "shardBy") <*> (o .:? "allocations"))
instance ToJSON TrafficSplit where
toJSON TrafficSplit{..}
= object
(catMaybes
[("shardBy" .=) <$> _tsShardBy,
("allocations" .=) <$> _tsAllocations])
newtype ScriptHandler = ScriptHandler
{ _shScriptPath :: Maybe Text
} deriving (Eq,Show,Data,Typeable,Generic)
scriptHandler
:: ScriptHandler
scriptHandler =
ScriptHandler
{ _shScriptPath = Nothing
}
shScriptPath :: Lens' ScriptHandler (Maybe Text)
shScriptPath
= lens _shScriptPath (\ s a -> s{_shScriptPath = a})
instance FromJSON ScriptHandler where
parseJSON
= withObject "ScriptHandler"
(\ o -> ScriptHandler <$> (o .:? "scriptPath"))
instance ToJSON ScriptHandler where
toJSON ScriptHandler{..}
= object
(catMaybes [("scriptPath" .=) <$> _shScriptPath])
data URLMap = URLMap
{ _umScript :: !(Maybe ScriptHandler)
, _umSecurityLevel :: !(Maybe Text)
, _umAPIEndpoint :: !(Maybe APIEndpointHandler)
, _umURLRegex :: !(Maybe Text)
, _umRedirectHTTPResponseCode :: !(Maybe Text)
, _umAuthFailAction :: !(Maybe Text)
, _umStaticFiles :: !(Maybe StaticFilesHandler)
, _umLogin :: !(Maybe Text)
, _umStaticDirectory :: !(Maybe StaticDirectoryHandler)
} deriving (Eq,Show,Data,Typeable,Generic)
urlMap
:: URLMap
urlMap =
URLMap
{ _umScript = Nothing
, _umSecurityLevel = Nothing
, _umAPIEndpoint = Nothing
, _umURLRegex = Nothing
, _umRedirectHTTPResponseCode = Nothing
, _umAuthFailAction = Nothing
, _umStaticFiles = Nothing
, _umLogin = Nothing
, _umStaticDirectory = Nothing
}
umScript :: Lens' URLMap (Maybe ScriptHandler)
umScript = lens _umScript (\ s a -> s{_umScript = a})
umSecurityLevel :: Lens' URLMap (Maybe Text)
umSecurityLevel
= lens _umSecurityLevel
(\ s a -> s{_umSecurityLevel = a})
umAPIEndpoint :: Lens' URLMap (Maybe APIEndpointHandler)
umAPIEndpoint
= lens _umAPIEndpoint
(\ s a -> s{_umAPIEndpoint = a})
umURLRegex :: Lens' URLMap (Maybe Text)
umURLRegex
= lens _umURLRegex (\ s a -> s{_umURLRegex = a})
umRedirectHTTPResponseCode :: Lens' URLMap (Maybe Text)
umRedirectHTTPResponseCode
= lens _umRedirectHTTPResponseCode
(\ s a -> s{_umRedirectHTTPResponseCode = a})
umAuthFailAction :: Lens' URLMap (Maybe Text)
umAuthFailAction
= lens _umAuthFailAction
(\ s a -> s{_umAuthFailAction = a})
umStaticFiles :: Lens' URLMap (Maybe StaticFilesHandler)
umStaticFiles
= lens _umStaticFiles
(\ s a -> s{_umStaticFiles = a})
umLogin :: Lens' URLMap (Maybe Text)
umLogin = lens _umLogin (\ s a -> s{_umLogin = a})
umStaticDirectory :: Lens' URLMap (Maybe StaticDirectoryHandler)
umStaticDirectory
= lens _umStaticDirectory
(\ s a -> s{_umStaticDirectory = a})
instance FromJSON URLMap where
parseJSON
= withObject "URLMap"
(\ o ->
URLMap <$>
(o .:? "script") <*> (o .:? "securityLevel") <*>
(o .:? "apiEndpoint")
<*> (o .:? "urlRegex")
<*> (o .:? "redirectHttpResponseCode")
<*> (o .:? "authFailAction")
<*> (o .:? "staticFiles")
<*> (o .:? "login")
<*> (o .:? "staticDirectory"))
instance ToJSON URLMap where
toJSON URLMap{..}
= object
(catMaybes
[("script" .=) <$> _umScript,
("securityLevel" .=) <$> _umSecurityLevel,
("apiEndpoint" .=) <$> _umAPIEndpoint,
("urlRegex" .=) <$> _umURLRegex,
("redirectHttpResponseCode" .=) <$>
_umRedirectHTTPResponseCode,
("authFailAction" .=) <$> _umAuthFailAction,
("staticFiles" .=) <$> _umStaticFiles,
("login" .=) <$> _umLogin,
("staticDirectory" .=) <$> _umStaticDirectory])
data Library = Library
{ _lName :: !(Maybe Text)
, _lVersion :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
library
:: Library
library =
Library
{ _lName = Nothing
, _lVersion = Nothing
}
lName :: Lens' Library (Maybe Text)
lName = lens _lName (\ s a -> s{_lName = a})
lVersion :: Lens' Library (Maybe Text)
lVersion = lens _lVersion (\ s a -> s{_lVersion = a})
instance FromJSON Library where
parseJSON
= withObject "Library"
(\ o ->
Library <$> (o .:? "name") <*> (o .:? "version"))
instance ToJSON Library where
toJSON Library{..}
= object
(catMaybes
[("name" .=) <$> _lName,
("version" .=) <$> _lVersion])
data ListOperationsResponse = ListOperationsResponse
{ _lorNextPageToken :: !(Maybe Text)
, _lorOperations :: !(Maybe [Operation])
} deriving (Eq,Show,Data,Typeable,Generic)
listOperationsResponse
:: ListOperationsResponse
listOperationsResponse =
ListOperationsResponse
{ _lorNextPageToken = Nothing
, _lorOperations = Nothing
}
lorNextPageToken :: Lens' ListOperationsResponse (Maybe Text)
lorNextPageToken
= lens _lorNextPageToken
(\ s a -> s{_lorNextPageToken = a})
lorOperations :: Lens' ListOperationsResponse [Operation]
lorOperations
= lens _lorOperations
(\ s a -> s{_lorOperations = a})
. _Default
. _Coerce
instance FromJSON ListOperationsResponse where
parseJSON
= withObject "ListOperationsResponse"
(\ o ->
ListOperationsResponse <$>
(o .:? "nextPageToken") <*>
(o .:? "operations" .!= mempty))
instance ToJSON ListOperationsResponse where
toJSON ListOperationsResponse{..}
= object
(catMaybes
[("nextPageToken" .=) <$> _lorNextPageToken,
("operations" .=) <$> _lorOperations])
data HealthCheck = HealthCheck
{ _hcHealthyThreshold :: !(Maybe (Textual Word32))
, _hcDisableHealthCheck :: !(Maybe Bool)
, _hcCheckInterval :: !(Maybe Text)
, _hcRestartThreshold :: !(Maybe (Textual Word32))
, _hcHost :: !(Maybe Text)
, _hcTimeout :: !(Maybe Text)
, _hcUnhealthyThreshold :: !(Maybe (Textual Word32))
} deriving (Eq,Show,Data,Typeable,Generic)
healthCheck
:: HealthCheck
healthCheck =
HealthCheck
{ _hcHealthyThreshold = Nothing
, _hcDisableHealthCheck = Nothing
, _hcCheckInterval = Nothing
, _hcRestartThreshold = Nothing
, _hcHost = Nothing
, _hcTimeout = Nothing
, _hcUnhealthyThreshold = Nothing
}
hcHealthyThreshold :: Lens' HealthCheck (Maybe Word32)
hcHealthyThreshold
= lens _hcHealthyThreshold
(\ s a -> s{_hcHealthyThreshold = a})
. mapping _Coerce
hcDisableHealthCheck :: Lens' HealthCheck (Maybe Bool)
hcDisableHealthCheck
= lens _hcDisableHealthCheck
(\ s a -> s{_hcDisableHealthCheck = a})
hcCheckInterval :: Lens' HealthCheck (Maybe Text)
hcCheckInterval
= lens _hcCheckInterval
(\ s a -> s{_hcCheckInterval = a})
hcRestartThreshold :: Lens' HealthCheck (Maybe Word32)
hcRestartThreshold
= lens _hcRestartThreshold
(\ s a -> s{_hcRestartThreshold = a})
. mapping _Coerce
hcHost :: Lens' HealthCheck (Maybe Text)
hcHost = lens _hcHost (\ s a -> s{_hcHost = a})
hcTimeout :: Lens' HealthCheck (Maybe Text)
hcTimeout
= lens _hcTimeout (\ s a -> s{_hcTimeout = a})
hcUnhealthyThreshold :: Lens' HealthCheck (Maybe Word32)
hcUnhealthyThreshold
= lens _hcUnhealthyThreshold
(\ s a -> s{_hcUnhealthyThreshold = a})
. mapping _Coerce
instance FromJSON HealthCheck where
parseJSON
= withObject "HealthCheck"
(\ o ->
HealthCheck <$>
(o .:? "healthyThreshold") <*>
(o .:? "disableHealthCheck")
<*> (o .:? "checkInterval")
<*> (o .:? "restartThreshold")
<*> (o .:? "host")
<*> (o .:? "timeout")
<*> (o .:? "unhealthyThreshold"))
instance ToJSON HealthCheck where
toJSON HealthCheck{..}
= object
(catMaybes
[("healthyThreshold" .=) <$> _hcHealthyThreshold,
("disableHealthCheck" .=) <$> _hcDisableHealthCheck,
("checkInterval" .=) <$> _hcCheckInterval,
("restartThreshold" .=) <$> _hcRestartThreshold,
("host" .=) <$> _hcHost,
("timeout" .=) <$> _hcTimeout,
("unhealthyThreshold" .=) <$> _hcUnhealthyThreshold])
data APIConfigHandler = APIConfigHandler
{ _achScript :: !(Maybe Text)
, _achSecurityLevel :: !(Maybe Text)
, _achURL :: !(Maybe Text)
, _achAuthFailAction :: !(Maybe Text)
, _achLogin :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
apiConfigHandler
:: APIConfigHandler
apiConfigHandler =
APIConfigHandler
{ _achScript = Nothing
, _achSecurityLevel = Nothing
, _achURL = Nothing
, _achAuthFailAction = Nothing
, _achLogin = Nothing
}
achScript :: Lens' APIConfigHandler (Maybe Text)
achScript
= lens _achScript (\ s a -> s{_achScript = a})
achSecurityLevel :: Lens' APIConfigHandler (Maybe Text)
achSecurityLevel
= lens _achSecurityLevel
(\ s a -> s{_achSecurityLevel = a})
achURL :: Lens' APIConfigHandler (Maybe Text)
achURL = lens _achURL (\ s a -> s{_achURL = a})
achAuthFailAction :: Lens' APIConfigHandler (Maybe Text)
achAuthFailAction
= lens _achAuthFailAction
(\ s a -> s{_achAuthFailAction = a})
achLogin :: Lens' APIConfigHandler (Maybe Text)
achLogin = lens _achLogin (\ s a -> s{_achLogin = a})
instance FromJSON APIConfigHandler where
parseJSON
= withObject "APIConfigHandler"
(\ o ->
APIConfigHandler <$>
(o .:? "script") <*> (o .:? "securityLevel") <*>
(o .:? "url")
<*> (o .:? "authFailAction")
<*> (o .:? "login"))
instance ToJSON APIConfigHandler where
toJSON APIConfigHandler{..}
= object
(catMaybes
[("script" .=) <$> _achScript,
("securityLevel" .=) <$> _achSecurityLevel,
("url" .=) <$> _achURL,
("authFailAction" .=) <$> _achAuthFailAction,
("login" .=) <$> _achLogin])
newtype VersionEnvVariables = VersionEnvVariables
{ _vevAddtional :: HashMap Text Text
} deriving (Eq,Show,Data,Typeable,Generic)
versionEnvVariables
:: HashMap Text Text
-> VersionEnvVariables
versionEnvVariables pVevAddtional_ =
VersionEnvVariables
{ _vevAddtional = _Coerce # pVevAddtional_
}
vevAddtional :: Lens' VersionEnvVariables (HashMap Text Text)
vevAddtional
= lens _vevAddtional (\ s a -> s{_vevAddtional = a})
. _Coerce
instance FromJSON VersionEnvVariables where
parseJSON
= withObject "VersionEnvVariables"
(\ o -> VersionEnvVariables <$> (parseJSONObject o))
instance ToJSON VersionEnvVariables where
toJSON = toJSON . _vevAddtional
data Application = Application
{ _aLocation :: !(Maybe Text)
, _aCodeBucket :: !(Maybe Text)
, _aName :: !(Maybe Text)
, _aDispatchRules :: !(Maybe [URLDispatchRule])
, _aId :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
application
:: Application
application =
Application
{ _aLocation = Nothing
, _aCodeBucket = Nothing
, _aName = Nothing
, _aDispatchRules = Nothing
, _aId = Nothing
}
aLocation :: Lens' Application (Maybe Text)
aLocation
= lens _aLocation (\ s a -> s{_aLocation = a})
aCodeBucket :: Lens' Application (Maybe Text)
aCodeBucket
= lens _aCodeBucket (\ s a -> s{_aCodeBucket = a})
aName :: Lens' Application (Maybe Text)
aName = lens _aName (\ s a -> s{_aName = a})
aDispatchRules :: Lens' Application [URLDispatchRule]
aDispatchRules
= lens _aDispatchRules
(\ s a -> s{_aDispatchRules = a})
. _Default
. _Coerce
aId :: Lens' Application (Maybe Text)
aId = lens _aId (\ s a -> s{_aId = a})
instance FromJSON Application where
parseJSON
= withObject "Application"
(\ o ->
Application <$>
(o .:? "location") <*> (o .:? "codeBucket") <*>
(o .:? "name")
<*> (o .:? "dispatchRules" .!= mempty)
<*> (o .:? "id"))
instance ToJSON Application where
toJSON Application{..}
= object
(catMaybes
[("location" .=) <$> _aLocation,
("codeBucket" .=) <$> _aCodeBucket,
("name" .=) <$> _aName,
("dispatchRules" .=) <$> _aDispatchRules,
("id" .=) <$> _aId])
newtype VersionBetaSettings = VersionBetaSettings
{ _vbsAddtional :: HashMap Text Text
} deriving (Eq,Show,Data,Typeable,Generic)
versionBetaSettings
:: HashMap Text Text
-> VersionBetaSettings
versionBetaSettings pVbsAddtional_ =
VersionBetaSettings
{ _vbsAddtional = _Coerce # pVbsAddtional_
}
vbsAddtional :: Lens' VersionBetaSettings (HashMap Text Text)
vbsAddtional
= lens _vbsAddtional (\ s a -> s{_vbsAddtional = a})
. _Coerce
instance FromJSON VersionBetaSettings where
parseJSON
= withObject "VersionBetaSettings"
(\ o -> VersionBetaSettings <$> (parseJSONObject o))
instance ToJSON VersionBetaSettings where
toJSON = toJSON . _vbsAddtional
data Operation = Operation
{ _oDone :: !(Maybe Bool)
, _oError :: !(Maybe Status)
, _oResponse :: !(Maybe OperationResponse)
, _oName :: !(Maybe Text)
, _oMetadata :: !(Maybe OperationSchema)
} deriving (Eq,Show,Data,Typeable,Generic)
operation
:: Operation
operation =
Operation
{ _oDone = Nothing
, _oError = Nothing
, _oResponse = Nothing
, _oName = Nothing
, _oMetadata = Nothing
}
oDone :: Lens' Operation (Maybe Bool)
oDone = lens _oDone (\ s a -> s{_oDone = a})
oError :: Lens' Operation (Maybe Status)
oError = lens _oError (\ s a -> s{_oError = a})
oResponse :: Lens' Operation (Maybe OperationResponse)
oResponse
= lens _oResponse (\ s a -> s{_oResponse = a})
oName :: Lens' Operation (Maybe Text)
oName = lens _oName (\ s a -> s{_oName = a})
oMetadata :: Lens' Operation (Maybe OperationSchema)
oMetadata
= lens _oMetadata (\ s a -> s{_oMetadata = a})
instance FromJSON Operation where
parseJSON
= withObject "Operation"
(\ o ->
Operation <$>
(o .:? "done") <*> (o .:? "error") <*>
(o .:? "response")
<*> (o .:? "name")
<*> (o .:? "metadata"))
instance ToJSON Operation where
toJSON Operation{..}
= object
(catMaybes
[("done" .=) <$> _oDone, ("error" .=) <$> _oError,
("response" .=) <$> _oResponse,
("name" .=) <$> _oName,
("metadata" .=) <$> _oMetadata])
data URLDispatchRule = URLDispatchRule
{ _udrPath :: !(Maybe Text)
, _udrDomain :: !(Maybe Text)
, _udrModule :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
urlDispatchRule
:: URLDispatchRule
urlDispatchRule =
URLDispatchRule
{ _udrPath = Nothing
, _udrDomain = Nothing
, _udrModule = Nothing
}
udrPath :: Lens' URLDispatchRule (Maybe Text)
udrPath = lens _udrPath (\ s a -> s{_udrPath = a})
udrDomain :: Lens' URLDispatchRule (Maybe Text)
udrDomain
= lens _udrDomain (\ s a -> s{_udrDomain = a})
udrModule :: Lens' URLDispatchRule (Maybe Text)
udrModule
= lens _udrModule (\ s a -> s{_udrModule = a})
instance FromJSON URLDispatchRule where
parseJSON
= withObject "URLDispatchRule"
(\ o ->
URLDispatchRule <$>
(o .:? "path") <*> (o .:? "domain") <*>
(o .:? "module"))
instance ToJSON URLDispatchRule where
toJSON URLDispatchRule{..}
= object
(catMaybes
[("path" .=) <$> _udrPath,
("domain" .=) <$> _udrDomain,
("module" .=) <$> _udrModule])
newtype StaticDirectoryHandlerHTTPHeaders = StaticDirectoryHandlerHTTPHeaders
{ _sdhhttphAddtional :: HashMap Text Text
} deriving (Eq,Show,Data,Typeable,Generic)
staticDirectoryHandlerHTTPHeaders
:: HashMap Text Text
-> StaticDirectoryHandlerHTTPHeaders
staticDirectoryHandlerHTTPHeaders pSdhhttphAddtional_ =
StaticDirectoryHandlerHTTPHeaders
{ _sdhhttphAddtional = _Coerce # pSdhhttphAddtional_
}
sdhhttphAddtional :: Lens' StaticDirectoryHandlerHTTPHeaders (HashMap Text Text)
sdhhttphAddtional
= lens _sdhhttphAddtional
(\ s a -> s{_sdhhttphAddtional = a})
. _Coerce
instance FromJSON StaticDirectoryHandlerHTTPHeaders
where
parseJSON
= withObject "StaticDirectoryHandlerHTTPHeaders"
(\ o ->
StaticDirectoryHandlerHTTPHeaders <$>
(parseJSONObject o))
instance ToJSON StaticDirectoryHandlerHTTPHeaders
where
toJSON = toJSON . _sdhhttphAddtional
data ListVersionsResponse = ListVersionsResponse
{ _lvrNextPageToken :: !(Maybe Text)
, _lvrVersions :: !(Maybe [Version])
} deriving (Eq,Show,Data,Typeable,Generic)
listVersionsResponse
:: ListVersionsResponse
listVersionsResponse =
ListVersionsResponse
{ _lvrNextPageToken = Nothing
, _lvrVersions = Nothing
}
lvrNextPageToken :: Lens' ListVersionsResponse (Maybe Text)
lvrNextPageToken
= lens _lvrNextPageToken
(\ s a -> s{_lvrNextPageToken = a})
lvrVersions :: Lens' ListVersionsResponse [Version]
lvrVersions
= lens _lvrVersions (\ s a -> s{_lvrVersions = a}) .
_Default
. _Coerce
instance FromJSON ListVersionsResponse where
parseJSON
= withObject "ListVersionsResponse"
(\ o ->
ListVersionsResponse <$>
(o .:? "nextPageToken") <*>
(o .:? "versions" .!= mempty))
instance ToJSON ListVersionsResponse where
toJSON ListVersionsResponse{..}
= object
(catMaybes
[("nextPageToken" .=) <$> _lvrNextPageToken,
("versions" .=) <$> _lvrVersions])
data FileInfo = FileInfo
{ _fiSha1Sum :: !(Maybe Text)
, _fiMimeType :: !(Maybe Text)
, _fiSourceURL :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
fileInfo
:: FileInfo
fileInfo =
FileInfo
{ _fiSha1Sum = Nothing
, _fiMimeType = Nothing
, _fiSourceURL = Nothing
}
fiSha1Sum :: Lens' FileInfo (Maybe Text)
fiSha1Sum
= lens _fiSha1Sum (\ s a -> s{_fiSha1Sum = a})
fiMimeType :: Lens' FileInfo (Maybe Text)
fiMimeType
= lens _fiMimeType (\ s a -> s{_fiMimeType = a})
fiSourceURL :: Lens' FileInfo (Maybe Text)
fiSourceURL
= lens _fiSourceURL (\ s a -> s{_fiSourceURL = a})
instance FromJSON FileInfo where
parseJSON
= withObject "FileInfo"
(\ o ->
FileInfo <$>
(o .:? "sha1Sum") <*> (o .:? "mimeType") <*>
(o .:? "sourceUrl"))
instance ToJSON FileInfo where
toJSON FileInfo{..}
= object
(catMaybes
[("sha1Sum" .=) <$> _fiSha1Sum,
("mimeType" .=) <$> _fiMimeType,
("sourceUrl" .=) <$> _fiSourceURL])
data AutomaticScaling = AutomaticScaling
{ _asMaxTotalInstances :: !(Maybe (Textual Int32))
, _asMinIdleInstances :: !(Maybe (Textual Int32))
, _asMinPendingLatency :: !(Maybe Text)
, _asCPUUtilization :: !(Maybe CPUUtilization)
, _asMaxIdleInstances :: !(Maybe (Textual Int32))
, _asMinTotalInstances :: !(Maybe (Textual Int32))
, _asMaxConcurrentRequests :: !(Maybe (Textual Int32))
, _asCoolDownPeriod :: !(Maybe Text)
, _asMaxPendingLatency :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
automaticScaling
:: AutomaticScaling
automaticScaling =
AutomaticScaling
{ _asMaxTotalInstances = Nothing
, _asMinIdleInstances = Nothing
, _asMinPendingLatency = Nothing
, _asCPUUtilization = Nothing
, _asMaxIdleInstances = Nothing
, _asMinTotalInstances = Nothing
, _asMaxConcurrentRequests = Nothing
, _asCoolDownPeriod = Nothing
, _asMaxPendingLatency = Nothing
}
asMaxTotalInstances :: Lens' AutomaticScaling (Maybe Int32)
asMaxTotalInstances
= lens _asMaxTotalInstances
(\ s a -> s{_asMaxTotalInstances = a})
. mapping _Coerce
asMinIdleInstances :: Lens' AutomaticScaling (Maybe Int32)
asMinIdleInstances
= lens _asMinIdleInstances
(\ s a -> s{_asMinIdleInstances = a})
. mapping _Coerce
asMinPendingLatency :: Lens' AutomaticScaling (Maybe Text)
asMinPendingLatency
= lens _asMinPendingLatency
(\ s a -> s{_asMinPendingLatency = a})
asCPUUtilization :: Lens' AutomaticScaling (Maybe CPUUtilization)
asCPUUtilization
= lens _asCPUUtilization
(\ s a -> s{_asCPUUtilization = a})
asMaxIdleInstances :: Lens' AutomaticScaling (Maybe Int32)
asMaxIdleInstances
= lens _asMaxIdleInstances
(\ s a -> s{_asMaxIdleInstances = a})
. mapping _Coerce
asMinTotalInstances :: Lens' AutomaticScaling (Maybe Int32)
asMinTotalInstances
= lens _asMinTotalInstances
(\ s a -> s{_asMinTotalInstances = a})
. mapping _Coerce
asMaxConcurrentRequests :: Lens' AutomaticScaling (Maybe Int32)
asMaxConcurrentRequests
= lens _asMaxConcurrentRequests
(\ s a -> s{_asMaxConcurrentRequests = a})
. mapping _Coerce
asCoolDownPeriod :: Lens' AutomaticScaling (Maybe Text)
asCoolDownPeriod
= lens _asCoolDownPeriod
(\ s a -> s{_asCoolDownPeriod = a})
asMaxPendingLatency :: Lens' AutomaticScaling (Maybe Text)
asMaxPendingLatency
= lens _asMaxPendingLatency
(\ s a -> s{_asMaxPendingLatency = a})
instance FromJSON AutomaticScaling where
parseJSON
= withObject "AutomaticScaling"
(\ o ->
AutomaticScaling <$>
(o .:? "maxTotalInstances") <*>
(o .:? "minIdleInstances")
<*> (o .:? "minPendingLatency")
<*> (o .:? "cpuUtilization")
<*> (o .:? "maxIdleInstances")
<*> (o .:? "minTotalInstances")
<*> (o .:? "maxConcurrentRequests")
<*> (o .:? "coolDownPeriod")
<*> (o .:? "maxPendingLatency"))
instance ToJSON AutomaticScaling where
toJSON AutomaticScaling{..}
= object
(catMaybes
[("maxTotalInstances" .=) <$> _asMaxTotalInstances,
("minIdleInstances" .=) <$> _asMinIdleInstances,
("minPendingLatency" .=) <$> _asMinPendingLatency,
("cpuUtilization" .=) <$> _asCPUUtilization,
("maxIdleInstances" .=) <$> _asMaxIdleInstances,
("minTotalInstances" .=) <$> _asMinTotalInstances,
("maxConcurrentRequests" .=) <$>
_asMaxConcurrentRequests,
("coolDownPeriod" .=) <$> _asCoolDownPeriod,
("maxPendingLatency" .=) <$> _asMaxPendingLatency])
data ListModulesResponse = ListModulesResponse
{ _lmrNextPageToken :: !(Maybe Text)
, _lmrModules :: !(Maybe [Module])
} deriving (Eq,Show,Data,Typeable,Generic)
listModulesResponse
:: ListModulesResponse
listModulesResponse =
ListModulesResponse
{ _lmrNextPageToken = Nothing
, _lmrModules = Nothing
}
lmrNextPageToken :: Lens' ListModulesResponse (Maybe Text)
lmrNextPageToken
= lens _lmrNextPageToken
(\ s a -> s{_lmrNextPageToken = a})
lmrModules :: Lens' ListModulesResponse [Module]
lmrModules
= lens _lmrModules (\ s a -> s{_lmrModules = a}) .
_Default
. _Coerce
instance FromJSON ListModulesResponse where
parseJSON
= withObject "ListModulesResponse"
(\ o ->
ListModulesResponse <$>
(o .:? "nextPageToken") <*>
(o .:? "modules" .!= mempty))
instance ToJSON ListModulesResponse where
toJSON ListModulesResponse{..}
= object
(catMaybes
[("nextPageToken" .=) <$> _lmrNextPageToken,
("modules" .=) <$> _lmrModules])
newtype APIEndpointHandler = APIEndpointHandler
{ _aehScriptPath :: Maybe Text
} deriving (Eq,Show,Data,Typeable,Generic)
apiEndpointHandler
:: APIEndpointHandler
apiEndpointHandler =
APIEndpointHandler
{ _aehScriptPath = Nothing
}
aehScriptPath :: Lens' APIEndpointHandler (Maybe Text)
aehScriptPath
= lens _aehScriptPath
(\ s a -> s{_aehScriptPath = a})
instance FromJSON APIEndpointHandler where
parseJSON
= withObject "APIEndpointHandler"
(\ o -> APIEndpointHandler <$> (o .:? "scriptPath"))
instance ToJSON APIEndpointHandler where
toJSON APIEndpointHandler{..}
= object
(catMaybes [("scriptPath" .=) <$> _aehScriptPath])
newtype StatusDetailsItem = StatusDetailsItem
{ _sdiAddtional :: HashMap Text JSONValue
} deriving (Eq,Show,Data,Typeable,Generic)
statusDetailsItem
:: HashMap Text JSONValue
-> StatusDetailsItem
statusDetailsItem pSdiAddtional_ =
StatusDetailsItem
{ _sdiAddtional = _Coerce # pSdiAddtional_
}
sdiAddtional :: Lens' StatusDetailsItem (HashMap Text JSONValue)
sdiAddtional
= lens _sdiAddtional (\ s a -> s{_sdiAddtional = a})
. _Coerce
instance FromJSON StatusDetailsItem where
parseJSON
= withObject "StatusDetailsItem"
(\ o -> StatusDetailsItem <$> (parseJSONObject o))
instance ToJSON StatusDetailsItem where
toJSON = toJSON . _sdiAddtional
data Network = Network
{ _nForwardedPorts :: !(Maybe [Text])
, _nInstanceTag :: !(Maybe Text)
, _nName :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
network
:: Network
network =
Network
{ _nForwardedPorts = Nothing
, _nInstanceTag = Nothing
, _nName = Nothing
}
nForwardedPorts :: Lens' Network [Text]
nForwardedPorts
= lens _nForwardedPorts
(\ s a -> s{_nForwardedPorts = a})
. _Default
. _Coerce
nInstanceTag :: Lens' Network (Maybe Text)
nInstanceTag
= lens _nInstanceTag (\ s a -> s{_nInstanceTag = a})
nName :: Lens' Network (Maybe Text)
nName = lens _nName (\ s a -> s{_nName = a})
instance FromJSON Network where
parseJSON
= withObject "Network"
(\ o ->
Network <$>
(o .:? "forwardedPorts" .!= mempty) <*>
(o .:? "instanceTag")
<*> (o .:? "name"))
instance ToJSON Network where
toJSON Network{..}
= object
(catMaybes
[("forwardedPorts" .=) <$> _nForwardedPorts,
("instanceTag" .=) <$> _nInstanceTag,
("name" .=) <$> _nName])
newtype StaticFilesHandlerHTTPHeaders = StaticFilesHandlerHTTPHeaders
{ _sfhhttphAddtional :: HashMap Text Text
} deriving (Eq,Show,Data,Typeable,Generic)
staticFilesHandlerHTTPHeaders
:: HashMap Text Text
-> StaticFilesHandlerHTTPHeaders
staticFilesHandlerHTTPHeaders pSfhhttphAddtional_ =
StaticFilesHandlerHTTPHeaders
{ _sfhhttphAddtional = _Coerce # pSfhhttphAddtional_
}
sfhhttphAddtional :: Lens' StaticFilesHandlerHTTPHeaders (HashMap Text Text)
sfhhttphAddtional
= lens _sfhhttphAddtional
(\ s a -> s{_sfhhttphAddtional = a})
. _Coerce
instance FromJSON StaticFilesHandlerHTTPHeaders where
parseJSON
= withObject "StaticFilesHandlerHTTPHeaders"
(\ o ->
StaticFilesHandlerHTTPHeaders <$>
(parseJSONObject o))
instance ToJSON StaticFilesHandlerHTTPHeaders where
toJSON = toJSON . _sfhhttphAddtional
data Resources = Resources
{ _rMemoryGb :: !(Maybe (Textual Double))
, _rDiskGb :: !(Maybe (Textual Double))
, _rCPU :: !(Maybe (Textual Double))
} deriving (Eq,Show,Data,Typeable,Generic)
resources
:: Resources
resources =
Resources
{ _rMemoryGb = Nothing
, _rDiskGb = Nothing
, _rCPU = Nothing
}
rMemoryGb :: Lens' Resources (Maybe Double)
rMemoryGb
= lens _rMemoryGb (\ s a -> s{_rMemoryGb = a}) .
mapping _Coerce
rDiskGb :: Lens' Resources (Maybe Double)
rDiskGb
= lens _rDiskGb (\ s a -> s{_rDiskGb = a}) .
mapping _Coerce
rCPU :: Lens' Resources (Maybe Double)
rCPU
= lens _rCPU (\ s a -> s{_rCPU = a}) .
mapping _Coerce
instance FromJSON Resources where
parseJSON
= withObject "Resources"
(\ o ->
Resources <$>
(o .:? "memoryGb") <*> (o .:? "diskGb") <*>
(o .:? "cpu"))
instance ToJSON Resources where
toJSON Resources{..}
= object
(catMaybes
[("memoryGb" .=) <$> _rMemoryGb,
("diskGb" .=) <$> _rDiskGb, ("cpu" .=) <$> _rCPU])
newtype DeploymentFiles = DeploymentFiles
{ _dfAddtional :: HashMap Text FileInfo
} deriving (Eq,Show,Data,Typeable,Generic)
deploymentFiles
:: HashMap Text FileInfo
-> DeploymentFiles
deploymentFiles pDfAddtional_ =
DeploymentFiles
{ _dfAddtional = _Coerce # pDfAddtional_
}
dfAddtional :: Lens' DeploymentFiles (HashMap Text FileInfo)
dfAddtional
= lens _dfAddtional (\ s a -> s{_dfAddtional = a}) .
_Coerce
instance FromJSON DeploymentFiles where
parseJSON
= withObject "DeploymentFiles"
(\ o -> DeploymentFiles <$> (parseJSONObject o))
instance ToJSON DeploymentFiles where
toJSON = toJSON . _dfAddtional
data CPUUtilization = CPUUtilization
{ _cuAggregationWindowLength :: !(Maybe Text)
, _cuTargetUtilization :: !(Maybe (Textual Double))
} deriving (Eq,Show,Data,Typeable,Generic)
cpuUtilization
:: CPUUtilization
cpuUtilization =
CPUUtilization
{ _cuAggregationWindowLength = Nothing
, _cuTargetUtilization = Nothing
}
cuAggregationWindowLength :: Lens' CPUUtilization (Maybe Text)
cuAggregationWindowLength
= lens _cuAggregationWindowLength
(\ s a -> s{_cuAggregationWindowLength = a})
cuTargetUtilization :: Lens' CPUUtilization (Maybe Double)
cuTargetUtilization
= lens _cuTargetUtilization
(\ s a -> s{_cuTargetUtilization = a})
. mapping _Coerce
instance FromJSON CPUUtilization where
parseJSON
= withObject "CPUUtilization"
(\ o ->
CPUUtilization <$>
(o .:? "aggregationWindowLength") <*>
(o .:? "targetUtilization"))
instance ToJSON CPUUtilization where
toJSON CPUUtilization{..}
= object
(catMaybes
[("aggregationWindowLength" .=) <$>
_cuAggregationWindowLength,
("targetUtilization" .=) <$> _cuTargetUtilization])
newtype TrafficSplitAllocations = TrafficSplitAllocations
{ _tsaAddtional :: HashMap Text (Textual Double)
} deriving (Eq,Show,Data,Typeable,Generic)
trafficSplitAllocations
:: HashMap Text Double
-> TrafficSplitAllocations
trafficSplitAllocations pTsaAddtional_ =
TrafficSplitAllocations
{ _tsaAddtional = _Coerce # pTsaAddtional_
}
tsaAddtional :: Lens' TrafficSplitAllocations (HashMap Text Double)
tsaAddtional
= lens _tsaAddtional (\ s a -> s{_tsaAddtional = a})
. _Coerce
instance FromJSON TrafficSplitAllocations where
parseJSON
= withObject "TrafficSplitAllocations"
(\ o ->
TrafficSplitAllocations <$> (parseJSONObject o))
instance ToJSON TrafficSplitAllocations where
toJSON = toJSON . _tsaAddtional
newtype ManualScaling = ManualScaling
{ _msInstances :: Maybe (Textual Int32)
} deriving (Eq,Show,Data,Typeable,Generic)
manualScaling
:: ManualScaling
manualScaling =
ManualScaling
{ _msInstances = Nothing
}
msInstances :: Lens' ManualScaling (Maybe Int32)
msInstances
= lens _msInstances (\ s a -> s{_msInstances = a}) .
mapping _Coerce
instance FromJSON ManualScaling where
parseJSON
= withObject "ManualScaling"
(\ o -> ManualScaling <$> (o .:? "instances"))
instance ToJSON ManualScaling where
toJSON ManualScaling{..}
= object
(catMaybes [("instances" .=) <$> _msInstances])
data BasicScaling = BasicScaling
{ _bsMaxInstances :: !(Maybe (Textual Int32))
, _bsIdleTimeout :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
basicScaling
:: BasicScaling
basicScaling =
BasicScaling
{ _bsMaxInstances = Nothing
, _bsIdleTimeout = Nothing
}
bsMaxInstances :: Lens' BasicScaling (Maybe Int32)
bsMaxInstances
= lens _bsMaxInstances
(\ s a -> s{_bsMaxInstances = a})
. mapping _Coerce
bsIdleTimeout :: Lens' BasicScaling (Maybe Text)
bsIdleTimeout
= lens _bsIdleTimeout
(\ s a -> s{_bsIdleTimeout = a})
instance FromJSON BasicScaling where
parseJSON
= withObject "BasicScaling"
(\ o ->
BasicScaling <$>
(o .:? "maxInstances") <*> (o .:? "idleTimeout"))
instance ToJSON BasicScaling where
toJSON BasicScaling{..}
= object
(catMaybes
[("maxInstances" .=) <$> _bsMaxInstances,
("idleTimeout" .=) <$> _bsIdleTimeout])
data Version = Version
{ _vCreationTime :: !(Maybe Text)
, _vRuntime :: !(Maybe Text)
, _vDeployer :: !(Maybe Text)
, _vNobuildFilesRegex :: !(Maybe Text)
, _vInstanceClass :: !(Maybe Text)
, _vHealthCheck :: !(Maybe HealthCheck)
, _vEnv :: !(Maybe Text)
, _vDefaultExpiration :: !(Maybe Text)
, _vAutomaticScaling :: !(Maybe AutomaticScaling)
, _vErrorHandlers :: !(Maybe [ErrorHandler])
, _vVM :: !(Maybe Bool)
, _vHandlers :: !(Maybe [URLMap])
, _vInboundServices :: !(Maybe [Text])
, _vNetwork :: !(Maybe Network)
, _vResources :: !(Maybe Resources)
, _vName :: !(Maybe Text)
, _vThreadsafe :: !(Maybe Bool)
, _vBetaSettings :: !(Maybe VersionBetaSettings)
, _vBasicScaling :: !(Maybe BasicScaling)
, _vManualScaling :: !(Maybe ManualScaling)
, _vAPIConfig :: !(Maybe APIConfigHandler)
, _vId :: !(Maybe Text)
, _vEnvVariables :: !(Maybe VersionEnvVariables)
, _vServingStatus :: !(Maybe Text)
, _vLibraries :: !(Maybe [Library])
, _vDeployment :: !(Maybe Deployment)
} deriving (Eq,Show,Data,Typeable,Generic)
version
:: Version
version =
Version
{ _vCreationTime = Nothing
, _vRuntime = Nothing
, _vDeployer = Nothing
, _vNobuildFilesRegex = Nothing
, _vInstanceClass = Nothing
, _vHealthCheck = Nothing
, _vEnv = Nothing
, _vDefaultExpiration = Nothing
, _vAutomaticScaling = Nothing
, _vErrorHandlers = Nothing
, _vVM = Nothing
, _vHandlers = Nothing
, _vInboundServices = Nothing
, _vNetwork = Nothing
, _vResources = Nothing
, _vName = Nothing
, _vThreadsafe = Nothing
, _vBetaSettings = Nothing
, _vBasicScaling = Nothing
, _vManualScaling = Nothing
, _vAPIConfig = Nothing
, _vId = Nothing
, _vEnvVariables = Nothing
, _vServingStatus = Nothing
, _vLibraries = Nothing
, _vDeployment = Nothing
}
vCreationTime :: Lens' Version (Maybe Text)
vCreationTime
= lens _vCreationTime
(\ s a -> s{_vCreationTime = a})
vRuntime :: Lens' Version (Maybe Text)
vRuntime = lens _vRuntime (\ s a -> s{_vRuntime = a})
vDeployer :: Lens' Version (Maybe Text)
vDeployer
= lens _vDeployer (\ s a -> s{_vDeployer = a})
vNobuildFilesRegex :: Lens' Version (Maybe Text)
vNobuildFilesRegex
= lens _vNobuildFilesRegex
(\ s a -> s{_vNobuildFilesRegex = a})
vInstanceClass :: Lens' Version (Maybe Text)
vInstanceClass
= lens _vInstanceClass
(\ s a -> s{_vInstanceClass = a})
vHealthCheck :: Lens' Version (Maybe HealthCheck)
vHealthCheck
= lens _vHealthCheck (\ s a -> s{_vHealthCheck = a})
vEnv :: Lens' Version (Maybe Text)
vEnv = lens _vEnv (\ s a -> s{_vEnv = a})
vDefaultExpiration :: Lens' Version (Maybe Text)
vDefaultExpiration
= lens _vDefaultExpiration
(\ s a -> s{_vDefaultExpiration = a})
vAutomaticScaling :: Lens' Version (Maybe AutomaticScaling)
vAutomaticScaling
= lens _vAutomaticScaling
(\ s a -> s{_vAutomaticScaling = a})
vErrorHandlers :: Lens' Version [ErrorHandler]
vErrorHandlers
= lens _vErrorHandlers
(\ s a -> s{_vErrorHandlers = a})
. _Default
. _Coerce
vVM :: Lens' Version (Maybe Bool)
vVM = lens _vVM (\ s a -> s{_vVM = a})
vHandlers :: Lens' Version [URLMap]
vHandlers
= lens _vHandlers (\ s a -> s{_vHandlers = a}) .
_Default
. _Coerce
vInboundServices :: Lens' Version [Text]
vInboundServices
= lens _vInboundServices
(\ s a -> s{_vInboundServices = a})
. _Default
. _Coerce
vNetwork :: Lens' Version (Maybe Network)
vNetwork = lens _vNetwork (\ s a -> s{_vNetwork = a})
vResources :: Lens' Version (Maybe Resources)
vResources
= lens _vResources (\ s a -> s{_vResources = a})
vName :: Lens' Version (Maybe Text)
vName = lens _vName (\ s a -> s{_vName = a})
vThreadsafe :: Lens' Version (Maybe Bool)
vThreadsafe
= lens _vThreadsafe (\ s a -> s{_vThreadsafe = a})
vBetaSettings :: Lens' Version (Maybe VersionBetaSettings)
vBetaSettings
= lens _vBetaSettings
(\ s a -> s{_vBetaSettings = a})
vBasicScaling :: Lens' Version (Maybe BasicScaling)
vBasicScaling
= lens _vBasicScaling
(\ s a -> s{_vBasicScaling = a})
vManualScaling :: Lens' Version (Maybe ManualScaling)
vManualScaling
= lens _vManualScaling
(\ s a -> s{_vManualScaling = a})
vAPIConfig :: Lens' Version (Maybe APIConfigHandler)
vAPIConfig
= lens _vAPIConfig (\ s a -> s{_vAPIConfig = a})
vId :: Lens' Version (Maybe Text)
vId = lens _vId (\ s a -> s{_vId = a})
vEnvVariables :: Lens' Version (Maybe VersionEnvVariables)
vEnvVariables
= lens _vEnvVariables
(\ s a -> s{_vEnvVariables = a})
vServingStatus :: Lens' Version (Maybe Text)
vServingStatus
= lens _vServingStatus
(\ s a -> s{_vServingStatus = a})
vLibraries :: Lens' Version [Library]
vLibraries
= lens _vLibraries (\ s a -> s{_vLibraries = a}) .
_Default
. _Coerce
vDeployment :: Lens' Version (Maybe Deployment)
vDeployment
= lens _vDeployment (\ s a -> s{_vDeployment = a})
instance FromJSON Version where
parseJSON
= withObject "Version"
(\ o ->
Version <$>
(o .:? "creationTime") <*> (o .:? "runtime") <*>
(o .:? "deployer")
<*> (o .:? "nobuildFilesRegex")
<*> (o .:? "instanceClass")
<*> (o .:? "healthCheck")
<*> (o .:? "env")
<*> (o .:? "defaultExpiration")
<*> (o .:? "automaticScaling")
<*> (o .:? "errorHandlers" .!= mempty)
<*> (o .:? "vm")
<*> (o .:? "handlers" .!= mempty)
<*> (o .:? "inboundServices" .!= mempty)
<*> (o .:? "network")
<*> (o .:? "resources")
<*> (o .:? "name")
<*> (o .:? "threadsafe")
<*> (o .:? "betaSettings")
<*> (o .:? "basicScaling")
<*> (o .:? "manualScaling")
<*> (o .:? "apiConfig")
<*> (o .:? "id")
<*> (o .:? "envVariables")
<*> (o .:? "servingStatus")
<*> (o .:? "libraries" .!= mempty)
<*> (o .:? "deployment"))
instance ToJSON Version where
toJSON Version{..}
= object
(catMaybes
[("creationTime" .=) <$> _vCreationTime,
("runtime" .=) <$> _vRuntime,
("deployer" .=) <$> _vDeployer,
("nobuildFilesRegex" .=) <$> _vNobuildFilesRegex,
("instanceClass" .=) <$> _vInstanceClass,
("healthCheck" .=) <$> _vHealthCheck,
("env" .=) <$> _vEnv,
("defaultExpiration" .=) <$> _vDefaultExpiration,
("automaticScaling" .=) <$> _vAutomaticScaling,
("errorHandlers" .=) <$> _vErrorHandlers,
("vm" .=) <$> _vVM, ("handlers" .=) <$> _vHandlers,
("inboundServices" .=) <$> _vInboundServices,
("network" .=) <$> _vNetwork,
("resources" .=) <$> _vResources,
("name" .=) <$> _vName,
("threadsafe" .=) <$> _vThreadsafe,
("betaSettings" .=) <$> _vBetaSettings,
("basicScaling" .=) <$> _vBasicScaling,
("manualScaling" .=) <$> _vManualScaling,
("apiConfig" .=) <$> _vAPIConfig, ("id" .=) <$> _vId,
("envVariables" .=) <$> _vEnvVariables,
("servingStatus" .=) <$> _vServingStatus,
("libraries" .=) <$> _vLibraries,
("deployment" .=) <$> _vDeployment])
data Module = Module
{ _mSplit :: !(Maybe TrafficSplit)
, _mName :: !(Maybe Text)
, _mId :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
module'
:: Module
module' =
Module
{ _mSplit = Nothing
, _mName = Nothing
, _mId = Nothing
}
mSplit :: Lens' Module (Maybe TrafficSplit)
mSplit = lens _mSplit (\ s a -> s{_mSplit = a})
mName :: Lens' Module (Maybe Text)
mName = lens _mName (\ s a -> s{_mName = a})
mId :: Lens' Module (Maybe Text)
mId = lens _mId (\ s a -> s{_mId = a})
instance FromJSON Module where
parseJSON
= withObject "Module"
(\ o ->
Module <$>
(o .:? "split") <*> (o .:? "name") <*> (o .:? "id"))
instance ToJSON Module where
toJSON Module{..}
= object
(catMaybes
[("split" .=) <$> _mSplit, ("name" .=) <$> _mName,
("id" .=) <$> _mId])
data StaticFilesHandler = StaticFilesHandler
{ _sfhHTTPHeaders :: !(Maybe StaticFilesHandlerHTTPHeaders)
, _sfhPath :: !(Maybe Text)
, _sfhRequireMatchingFile :: !(Maybe Bool)
, _sfhExpiration :: !(Maybe Text)
, _sfhMimeType :: !(Maybe Text)
, _sfhApplicationReadable :: !(Maybe Bool)
, _sfhUploadPathRegex :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
staticFilesHandler
:: StaticFilesHandler
staticFilesHandler =
StaticFilesHandler
{ _sfhHTTPHeaders = Nothing
, _sfhPath = Nothing
, _sfhRequireMatchingFile = Nothing
, _sfhExpiration = Nothing
, _sfhMimeType = Nothing
, _sfhApplicationReadable = Nothing
, _sfhUploadPathRegex = Nothing
}
sfhHTTPHeaders :: Lens' StaticFilesHandler (Maybe StaticFilesHandlerHTTPHeaders)
sfhHTTPHeaders
= lens _sfhHTTPHeaders
(\ s a -> s{_sfhHTTPHeaders = a})
sfhPath :: Lens' StaticFilesHandler (Maybe Text)
sfhPath = lens _sfhPath (\ s a -> s{_sfhPath = a})
sfhRequireMatchingFile :: Lens' StaticFilesHandler (Maybe Bool)
sfhRequireMatchingFile
= lens _sfhRequireMatchingFile
(\ s a -> s{_sfhRequireMatchingFile = a})
sfhExpiration :: Lens' StaticFilesHandler (Maybe Text)
sfhExpiration
= lens _sfhExpiration
(\ s a -> s{_sfhExpiration = a})
sfhMimeType :: Lens' StaticFilesHandler (Maybe Text)
sfhMimeType
= lens _sfhMimeType (\ s a -> s{_sfhMimeType = a})
sfhApplicationReadable :: Lens' StaticFilesHandler (Maybe Bool)
sfhApplicationReadable
= lens _sfhApplicationReadable
(\ s a -> s{_sfhApplicationReadable = a})
sfhUploadPathRegex :: Lens' StaticFilesHandler (Maybe Text)
sfhUploadPathRegex
= lens _sfhUploadPathRegex
(\ s a -> s{_sfhUploadPathRegex = a})
instance FromJSON StaticFilesHandler where
parseJSON
= withObject "StaticFilesHandler"
(\ o ->
StaticFilesHandler <$>
(o .:? "httpHeaders") <*> (o .:? "path") <*>
(o .:? "requireMatchingFile")
<*> (o .:? "expiration")
<*> (o .:? "mimeType")
<*> (o .:? "applicationReadable")
<*> (o .:? "uploadPathRegex"))
instance ToJSON StaticFilesHandler where
toJSON StaticFilesHandler{..}
= object
(catMaybes
[("httpHeaders" .=) <$> _sfhHTTPHeaders,
("path" .=) <$> _sfhPath,
("requireMatchingFile" .=) <$>
_sfhRequireMatchingFile,
("expiration" .=) <$> _sfhExpiration,
("mimeType" .=) <$> _sfhMimeType,
("applicationReadable" .=) <$>
_sfhApplicationReadable,
("uploadPathRegex" .=) <$> _sfhUploadPathRegex])
data ErrorHandler = ErrorHandler
{ _ehMimeType :: !(Maybe Text)
, _ehErrorCode :: !(Maybe Text)
, _ehStaticFile :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
errorHandler
:: ErrorHandler
errorHandler =
ErrorHandler
{ _ehMimeType = Nothing
, _ehErrorCode = Nothing
, _ehStaticFile = Nothing
}
ehMimeType :: Lens' ErrorHandler (Maybe Text)
ehMimeType
= lens _ehMimeType (\ s a -> s{_ehMimeType = a})
ehErrorCode :: Lens' ErrorHandler (Maybe Text)
ehErrorCode
= lens _ehErrorCode (\ s a -> s{_ehErrorCode = a})
ehStaticFile :: Lens' ErrorHandler (Maybe Text)
ehStaticFile
= lens _ehStaticFile (\ s a -> s{_ehStaticFile = a})
instance FromJSON ErrorHandler where
parseJSON
= withObject "ErrorHandler"
(\ o ->
ErrorHandler <$>
(o .:? "mimeType") <*> (o .:? "errorCode") <*>
(o .:? "staticFile"))
instance ToJSON ErrorHandler where
toJSON ErrorHandler{..}
= object
(catMaybes
[("mimeType" .=) <$> _ehMimeType,
("errorCode" .=) <$> _ehErrorCode,
("staticFile" .=) <$> _ehStaticFile])
data OperationMetadata = OperationMetadata
{ _omInsertTime :: !(Maybe Text)
, _omUser :: !(Maybe Text)
, _omMethod :: !(Maybe Text)
, _omEndTime :: !(Maybe Text)
, _omOperationType :: !(Maybe Text)
, _omTarget :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
operationMetadata
:: OperationMetadata
operationMetadata =
OperationMetadata
{ _omInsertTime = Nothing
, _omUser = Nothing
, _omMethod = Nothing
, _omEndTime = Nothing
, _omOperationType = Nothing
, _omTarget = Nothing
}
omInsertTime :: Lens' OperationMetadata (Maybe Text)
omInsertTime
= lens _omInsertTime (\ s a -> s{_omInsertTime = a})
omUser :: Lens' OperationMetadata (Maybe Text)
omUser = lens _omUser (\ s a -> s{_omUser = a})
omMethod :: Lens' OperationMetadata (Maybe Text)
omMethod = lens _omMethod (\ s a -> s{_omMethod = a})
omEndTime :: Lens' OperationMetadata (Maybe Text)
omEndTime
= lens _omEndTime (\ s a -> s{_omEndTime = a})
omOperationType :: Lens' OperationMetadata (Maybe Text)
omOperationType
= lens _omOperationType
(\ s a -> s{_omOperationType = a})
omTarget :: Lens' OperationMetadata (Maybe Text)
omTarget = lens _omTarget (\ s a -> s{_omTarget = a})
instance FromJSON OperationMetadata where
parseJSON
= withObject "OperationMetadata"
(\ o ->
OperationMetadata <$>
(o .:? "insertTime") <*> (o .:? "user") <*>
(o .:? "method")
<*> (o .:? "endTime")
<*> (o .:? "operationType")
<*> (o .:? "target"))
instance ToJSON OperationMetadata where
toJSON OperationMetadata{..}
= object
(catMaybes
[("insertTime" .=) <$> _omInsertTime,
("user" .=) <$> _omUser, ("method" .=) <$> _omMethod,
("endTime" .=) <$> _omEndTime,
("operationType" .=) <$> _omOperationType,
("target" .=) <$> _omTarget])
data SourceReference = SourceReference
{ _srRepository :: !(Maybe Text)
, _srRevisionId :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
sourceReference
:: SourceReference
sourceReference =
SourceReference
{ _srRepository = Nothing
, _srRevisionId = Nothing
}
srRepository :: Lens' SourceReference (Maybe Text)
srRepository
= lens _srRepository (\ s a -> s{_srRepository = a})
srRevisionId :: Lens' SourceReference (Maybe Text)
srRevisionId
= lens _srRevisionId (\ s a -> s{_srRevisionId = a})
instance FromJSON SourceReference where
parseJSON
= withObject "SourceReference"
(\ o ->
SourceReference <$>
(o .:? "repository") <*> (o .:? "revisionId"))
instance ToJSON SourceReference where
toJSON SourceReference{..}
= object
(catMaybes
[("repository" .=) <$> _srRepository,
("revisionId" .=) <$> _srRevisionId])
newtype OperationResponse = OperationResponse
{ _orAddtional :: HashMap Text JSONValue
} deriving (Eq,Show,Data,Typeable,Generic)
operationResponse
:: HashMap Text JSONValue
-> OperationResponse
operationResponse pOrAddtional_ =
OperationResponse
{ _orAddtional = _Coerce # pOrAddtional_
}
orAddtional :: Lens' OperationResponse (HashMap Text JSONValue)
orAddtional
= lens _orAddtional (\ s a -> s{_orAddtional = a}) .
_Coerce
instance FromJSON OperationResponse where
parseJSON
= withObject "OperationResponse"
(\ o -> OperationResponse <$> (parseJSONObject o))
instance ToJSON OperationResponse where
toJSON = toJSON . _orAddtional
newtype ContainerInfo = ContainerInfo
{ _ciImage :: Maybe Text
} deriving (Eq,Show,Data,Typeable,Generic)
containerInfo
:: ContainerInfo
containerInfo =
ContainerInfo
{ _ciImage = Nothing
}
ciImage :: Lens' ContainerInfo (Maybe Text)
ciImage = lens _ciImage (\ s a -> s{_ciImage = a})
instance FromJSON ContainerInfo where
parseJSON
= withObject "ContainerInfo"
(\ o -> ContainerInfo <$> (o .:? "image"))
instance ToJSON ContainerInfo where
toJSON ContainerInfo{..}
= object (catMaybes [("image" .=) <$> _ciImage])
data Deployment = Deployment
{ _dContainer :: !(Maybe ContainerInfo)
, _dFiles :: !(Maybe DeploymentFiles)
, _dSourceReferences :: !(Maybe [SourceReference])
} deriving (Eq,Show,Data,Typeable,Generic)
deployment
:: Deployment
deployment =
Deployment
{ _dContainer = Nothing
, _dFiles = Nothing
, _dSourceReferences = Nothing
}
dContainer :: Lens' Deployment (Maybe ContainerInfo)
dContainer
= lens _dContainer (\ s a -> s{_dContainer = a})
dFiles :: Lens' Deployment (Maybe DeploymentFiles)
dFiles = lens _dFiles (\ s a -> s{_dFiles = a})
dSourceReferences :: Lens' Deployment [SourceReference]
dSourceReferences
= lens _dSourceReferences
(\ s a -> s{_dSourceReferences = a})
. _Default
. _Coerce
instance FromJSON Deployment where
parseJSON
= withObject "Deployment"
(\ o ->
Deployment <$>
(o .:? "container") <*> (o .:? "files") <*>
(o .:? "sourceReferences" .!= mempty))
instance ToJSON Deployment where
toJSON Deployment{..}
= object
(catMaybes
[("container" .=) <$> _dContainer,
("files" .=) <$> _dFiles,
("sourceReferences" .=) <$> _dSourceReferences])
data StaticDirectoryHandler = StaticDirectoryHandler
{ _sdhHTTPHeaders :: !(Maybe StaticDirectoryHandlerHTTPHeaders)
, _sdhRequireMatchingFile :: !(Maybe Bool)
, _sdhExpiration :: !(Maybe Text)
, _sdhMimeType :: !(Maybe Text)
, _sdhApplicationReadable :: !(Maybe Bool)
, _sdhDirectory :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
staticDirectoryHandler
:: StaticDirectoryHandler
staticDirectoryHandler =
StaticDirectoryHandler
{ _sdhHTTPHeaders = Nothing
, _sdhRequireMatchingFile = Nothing
, _sdhExpiration = Nothing
, _sdhMimeType = Nothing
, _sdhApplicationReadable = Nothing
, _sdhDirectory = Nothing
}
sdhHTTPHeaders :: Lens' StaticDirectoryHandler (Maybe StaticDirectoryHandlerHTTPHeaders)
sdhHTTPHeaders
= lens _sdhHTTPHeaders
(\ s a -> s{_sdhHTTPHeaders = a})
sdhRequireMatchingFile :: Lens' StaticDirectoryHandler (Maybe Bool)
sdhRequireMatchingFile
= lens _sdhRequireMatchingFile
(\ s a -> s{_sdhRequireMatchingFile = a})
sdhExpiration :: Lens' StaticDirectoryHandler (Maybe Text)
sdhExpiration
= lens _sdhExpiration
(\ s a -> s{_sdhExpiration = a})
sdhMimeType :: Lens' StaticDirectoryHandler (Maybe Text)
sdhMimeType
= lens _sdhMimeType (\ s a -> s{_sdhMimeType = a})
sdhApplicationReadable :: Lens' StaticDirectoryHandler (Maybe Bool)
sdhApplicationReadable
= lens _sdhApplicationReadable
(\ s a -> s{_sdhApplicationReadable = a})
sdhDirectory :: Lens' StaticDirectoryHandler (Maybe Text)
sdhDirectory
= lens _sdhDirectory (\ s a -> s{_sdhDirectory = a})
instance FromJSON StaticDirectoryHandler where
parseJSON
= withObject "StaticDirectoryHandler"
(\ o ->
StaticDirectoryHandler <$>
(o .:? "httpHeaders") <*>
(o .:? "requireMatchingFile")
<*> (o .:? "expiration")
<*> (o .:? "mimeType")
<*> (o .:? "applicationReadable")
<*> (o .:? "directory"))
instance ToJSON StaticDirectoryHandler where
toJSON StaticDirectoryHandler{..}
= object
(catMaybes
[("httpHeaders" .=) <$> _sdhHTTPHeaders,
("requireMatchingFile" .=) <$>
_sdhRequireMatchingFile,
("expiration" .=) <$> _sdhExpiration,
("mimeType" .=) <$> _sdhMimeType,
("applicationReadable" .=) <$>
_sdhApplicationReadable,
("directory" .=) <$> _sdhDirectory])