{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Network.Google.Blogger.Types.Sum where
import Network.Google.Prelude hiding (Bytes)
data PostsListOrderBy
= Published
| Updated
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable PostsListOrderBy
instance FromHttpApiData PostsListOrderBy where
parseQueryParam = \case
"published" -> Right Published
"updated" -> Right Updated
x -> Left ("Unable to parse PostsListOrderBy from: " <> x)
instance ToHttpApiData PostsListOrderBy where
toQueryParam = \case
Published -> "published"
Updated -> "updated"
instance FromJSON PostsListOrderBy where
parseJSON = parseJSONText "PostsListOrderBy"
instance ToJSON PostsListOrderBy where
toJSON = toJSONText
data PostsListView
= Admin
| Author
| Reader
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable PostsListView
instance FromHttpApiData PostsListView where
parseQueryParam = \case
"ADMIN" -> Right Admin
"AUTHOR" -> Right Author
"READER" -> Right Reader
x -> Left ("Unable to parse PostsListView from: " <> x)
instance ToHttpApiData PostsListView where
toQueryParam = \case
Admin -> "ADMIN"
Author -> "AUTHOR"
Reader -> "READER"
instance FromJSON PostsListView where
parseJSON = parseJSONText "PostsListView"
instance ToJSON PostsListView where
toJSON = toJSONText
data PageViewsGetRange
= PVGR30DAYS
| PVGR7DAYS
| PVGRAll
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable PageViewsGetRange
instance FromHttpApiData PageViewsGetRange where
parseQueryParam = \case
"30DAYS" -> Right PVGR30DAYS
"7DAYS" -> Right PVGR7DAYS
"all" -> Right PVGRAll
x -> Left ("Unable to parse PageViewsGetRange from: " <> x)
instance ToHttpApiData PageViewsGetRange where
toQueryParam = \case
PVGR30DAYS -> "30DAYS"
PVGR7DAYS -> "7DAYS"
PVGRAll -> "all"
instance FromJSON PageViewsGetRange where
parseJSON = parseJSONText "PageViewsGetRange"
instance ToJSON PageViewsGetRange where
toJSON = toJSONText
data CommentsListView
= CLVAdmin
| CLVAuthor
| CLVReader
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable CommentsListView
instance FromHttpApiData CommentsListView where
parseQueryParam = \case
"ADMIN" -> Right CLVAdmin
"AUTHOR" -> Right CLVAuthor
"READER" -> Right CLVReader
x -> Left ("Unable to parse CommentsListView from: " <> x)
instance ToHttpApiData CommentsListView where
toQueryParam = \case
CLVAdmin -> "ADMIN"
CLVAuthor -> "AUTHOR"
CLVReader -> "READER"
instance FromJSON CommentsListView where
parseJSON = parseJSONText "CommentsListView"
instance ToJSON CommentsListView where
toJSON = toJSONText
data PostUserInfosListStatus
= Draft
| Live
| Scheduled
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable PostUserInfosListStatus
instance FromHttpApiData PostUserInfosListStatus where
parseQueryParam = \case
"draft" -> Right Draft
"live" -> Right Live
"scheduled" -> Right Scheduled
x -> Left ("Unable to parse PostUserInfosListStatus from: " <> x)
instance ToHttpApiData PostUserInfosListStatus where
toQueryParam = \case
Draft -> "draft"
Live -> "live"
Scheduled -> "scheduled"
instance FromJSON PostUserInfosListStatus where
parseJSON = parseJSONText "PostUserInfosListStatus"
instance ToJSON PostUserInfosListStatus where
toJSON = toJSONText
data PostsGetView
= PGVAdmin
| PGVAuthor
| PGVReader
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable PostsGetView
instance FromHttpApiData PostsGetView where
parseQueryParam = \case
"ADMIN" -> Right PGVAdmin
"AUTHOR" -> Right PGVAuthor
"READER" -> Right PGVReader
x -> Left ("Unable to parse PostsGetView from: " <> x)
instance ToHttpApiData PostsGetView where
toQueryParam = \case
PGVAdmin -> "ADMIN"
PGVAuthor -> "AUTHOR"
PGVReader -> "READER"
instance FromJSON PostsGetView where
parseJSON = parseJSONText "PostsGetView"
instance ToJSON PostsGetView where
toJSON = toJSONText
data PostsSearchOrderBy
= PSOBPublished
| PSOBUpdated
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable PostsSearchOrderBy
instance FromHttpApiData PostsSearchOrderBy where
parseQueryParam = \case
"published" -> Right PSOBPublished
"updated" -> Right PSOBUpdated
x -> Left ("Unable to parse PostsSearchOrderBy from: " <> x)
instance ToHttpApiData PostsSearchOrderBy where
toQueryParam = \case
PSOBPublished -> "published"
PSOBUpdated -> "updated"
instance FromJSON PostsSearchOrderBy where
parseJSON = parseJSONText "PostsSearchOrderBy"
instance ToJSON PostsSearchOrderBy where
toJSON = toJSONText
data CommentsListByBlogStatus
= CLBBSEmptied
| CLBBSLive
| CLBBSPending
| CLBBSSpam
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable CommentsListByBlogStatus
instance FromHttpApiData CommentsListByBlogStatus where
parseQueryParam = \case
"emptied" -> Right CLBBSEmptied
"live" -> Right CLBBSLive
"pending" -> Right CLBBSPending
"spam" -> Right CLBBSSpam
x -> Left ("Unable to parse CommentsListByBlogStatus from: " <> x)
instance ToHttpApiData CommentsListByBlogStatus where
toQueryParam = \case
CLBBSEmptied -> "emptied"
CLBBSLive -> "live"
CLBBSPending -> "pending"
CLBBSSpam -> "spam"
instance FromJSON CommentsListByBlogStatus where
parseJSON = parseJSONText "CommentsListByBlogStatus"
instance ToJSON CommentsListByBlogStatus where
toJSON = toJSONText
data PagesGetView
= PAdmin
| PAuthor
| PReader
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable PagesGetView
instance FromHttpApiData PagesGetView where
parseQueryParam = \case
"ADMIN" -> Right PAdmin
"AUTHOR" -> Right PAuthor
"READER" -> Right PReader
x -> Left ("Unable to parse PagesGetView from: " <> x)
instance ToHttpApiData PagesGetView where
toQueryParam = \case
PAdmin -> "ADMIN"
PAuthor -> "AUTHOR"
PReader -> "READER"
instance FromJSON PagesGetView where
parseJSON = parseJSONText "PagesGetView"
instance ToJSON PagesGetView where
toJSON = toJSONText
data PostUserInfosListOrderBy
= PUILOBPublished
| PUILOBUpdated
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable PostUserInfosListOrderBy
instance FromHttpApiData PostUserInfosListOrderBy where
parseQueryParam = \case
"published" -> Right PUILOBPublished
"updated" -> Right PUILOBUpdated
x -> Left ("Unable to parse PostUserInfosListOrderBy from: " <> x)
instance ToHttpApiData PostUserInfosListOrderBy where
toQueryParam = \case
PUILOBPublished -> "published"
PUILOBUpdated -> "updated"
instance FromJSON PostUserInfosListOrderBy where
parseJSON = parseJSONText "PostUserInfosListOrderBy"
instance ToJSON PostUserInfosListOrderBy where
toJSON = toJSONText
data BlogsGetView
= BGVAdmin
| BGVAuthor
| BGVReader
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable BlogsGetView
instance FromHttpApiData BlogsGetView where
parseQueryParam = \case
"ADMIN" -> Right BGVAdmin
"AUTHOR" -> Right BGVAuthor
"READER" -> Right BGVReader
x -> Left ("Unable to parse BlogsGetView from: " <> x)
instance ToHttpApiData BlogsGetView where
toQueryParam = \case
BGVAdmin -> "ADMIN"
BGVAuthor -> "AUTHOR"
BGVReader -> "READER"
instance FromJSON BlogsGetView where
parseJSON = parseJSONText "BlogsGetView"
instance ToJSON BlogsGetView where
toJSON = toJSONText
data BlogsGetByURLView
= BGBUVAdmin
| BGBUVAuthor
| BGBUVReader
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable BlogsGetByURLView
instance FromHttpApiData BlogsGetByURLView where
parseQueryParam = \case
"ADMIN" -> Right BGBUVAdmin
"AUTHOR" -> Right BGBUVAuthor
"READER" -> Right BGBUVReader
x -> Left ("Unable to parse BlogsGetByURLView from: " <> x)
instance ToHttpApiData BlogsGetByURLView where
toQueryParam = \case
BGBUVAdmin -> "ADMIN"
BGBUVAuthor -> "AUTHOR"
BGBUVReader -> "READER"
instance FromJSON BlogsGetByURLView where
parseJSON = parseJSONText "BlogsGetByURLView"
instance ToJSON BlogsGetByURLView where
toJSON = toJSONText
data CommentsListStatus
= CLSEmptied
| CLSLive
| CLSPending
| CLSSpam
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable CommentsListStatus
instance FromHttpApiData CommentsListStatus where
parseQueryParam = \case
"emptied" -> Right CLSEmptied
"live" -> Right CLSLive
"pending" -> Right CLSPending
"spam" -> Right CLSSpam
x -> Left ("Unable to parse CommentsListStatus from: " <> x)
instance ToHttpApiData CommentsListStatus where
toQueryParam = \case
CLSEmptied -> "emptied"
CLSLive -> "live"
CLSPending -> "pending"
CLSSpam -> "spam"
instance FromJSON CommentsListStatus where
parseJSON = parseJSONText "CommentsListStatus"
instance ToJSON CommentsListStatus where
toJSON = toJSONText
data BlogsListByUserStatus
= BLBUSDeleted
| BLBUSLive
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable BlogsListByUserStatus
instance FromHttpApiData BlogsListByUserStatus where
parseQueryParam = \case
"DELETED" -> Right BLBUSDeleted
"LIVE" -> Right BLBUSLive
x -> Left ("Unable to parse BlogsListByUserStatus from: " <> x)
instance ToHttpApiData BlogsListByUserStatus where
toQueryParam = \case
BLBUSDeleted -> "DELETED"
BLBUSLive -> "LIVE"
instance FromJSON BlogsListByUserStatus where
parseJSON = parseJSONText "BlogsListByUserStatus"
instance ToJSON BlogsListByUserStatus where
toJSON = toJSONText
data PagesListView
= PLVAdmin
| PLVAuthor
| PLVReader
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable PagesListView
instance FromHttpApiData PagesListView where
parseQueryParam = \case
"ADMIN" -> Right PLVAdmin
"AUTHOR" -> Right PLVAuthor
"READER" -> Right PLVReader
x -> Left ("Unable to parse PagesListView from: " <> x)
instance ToHttpApiData PagesListView where
toQueryParam = \case
PLVAdmin -> "ADMIN"
PLVAuthor -> "AUTHOR"
PLVReader -> "READER"
instance FromJSON PagesListView where
parseJSON = parseJSONText "PagesListView"
instance ToJSON PagesListView where
toJSON = toJSONText
data PostsListStatus
= PLSDraft
| PLSLive
| PLSScheduled
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable PostsListStatus
instance FromHttpApiData PostsListStatus where
parseQueryParam = \case
"draft" -> Right PLSDraft
"live" -> Right PLSLive
"scheduled" -> Right PLSScheduled
x -> Left ("Unable to parse PostsListStatus from: " <> x)
instance ToHttpApiData PostsListStatus where
toQueryParam = \case
PLSDraft -> "draft"
PLSLive -> "live"
PLSScheduled -> "scheduled"
instance FromJSON PostsListStatus where
parseJSON = parseJSONText "PostsListStatus"
instance ToJSON PostsListStatus where
toJSON = toJSONText
data BlogsListByUserView
= BLBUVAdmin
| BLBUVAuthor
| BLBUVReader
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable BlogsListByUserView
instance FromHttpApiData BlogsListByUserView where
parseQueryParam = \case
"ADMIN" -> Right BLBUVAdmin
"AUTHOR" -> Right BLBUVAuthor
"READER" -> Right BLBUVReader
x -> Left ("Unable to parse BlogsListByUserView from: " <> x)
instance ToHttpApiData BlogsListByUserView where
toQueryParam = \case
BLBUVAdmin -> "ADMIN"
BLBUVAuthor -> "AUTHOR"
BLBUVReader -> "READER"
instance FromJSON BlogsListByUserView where
parseJSON = parseJSONText "BlogsListByUserView"
instance ToJSON BlogsListByUserView where
toJSON = toJSONText
data PostUserInfosListView
= PUILVAdmin
| PUILVAuthor
| PUILVReader
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable PostUserInfosListView
instance FromHttpApiData PostUserInfosListView where
parseQueryParam = \case
"ADMIN" -> Right PUILVAdmin
"AUTHOR" -> Right PUILVAuthor
"READER" -> Right PUILVReader
x -> Left ("Unable to parse PostUserInfosListView from: " <> x)
instance ToHttpApiData PostUserInfosListView where
toQueryParam = \case
PUILVAdmin -> "ADMIN"
PUILVAuthor -> "AUTHOR"
PUILVReader -> "READER"
instance FromJSON PostUserInfosListView where
parseJSON = parseJSONText "PostUserInfosListView"
instance ToJSON PostUserInfosListView where
toJSON = toJSONText
data CommentsGetView
= CGVAdmin
| CGVAuthor
| CGVReader
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable CommentsGetView
instance FromHttpApiData CommentsGetView where
parseQueryParam = \case
"ADMIN" -> Right CGVAdmin
"AUTHOR" -> Right CGVAuthor
"READER" -> Right CGVReader
x -> Left ("Unable to parse CommentsGetView from: " <> x)
instance ToHttpApiData CommentsGetView where
toQueryParam = \case
CGVAdmin -> "ADMIN"
CGVAuthor -> "AUTHOR"
CGVReader -> "READER"
instance FromJSON CommentsGetView where
parseJSON = parseJSONText "CommentsGetView"
instance ToJSON CommentsGetView where
toJSON = toJSONText
data PostsGetByPathView
= PGBPVAdmin
| PGBPVAuthor
| PGBPVReader
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable PostsGetByPathView
instance FromHttpApiData PostsGetByPathView where
parseQueryParam = \case
"ADMIN" -> Right PGBPVAdmin
"AUTHOR" -> Right PGBPVAuthor
"READER" -> Right PGBPVReader
x -> Left ("Unable to parse PostsGetByPathView from: " <> x)
instance ToHttpApiData PostsGetByPathView where
toQueryParam = \case
PGBPVAdmin -> "ADMIN"
PGBPVAuthor -> "AUTHOR"
PGBPVReader -> "READER"
instance FromJSON PostsGetByPathView where
parseJSON = parseJSONText "PostsGetByPathView"
instance ToJSON PostsGetByPathView where
toJSON = toJSONText
data PagesListStatus
= PDraft
| PLive
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable PagesListStatus
instance FromHttpApiData PagesListStatus where
parseQueryParam = \case
"draft" -> Right PDraft
"live" -> Right PLive
x -> Left ("Unable to parse PagesListStatus from: " <> x)
instance ToHttpApiData PagesListStatus where
toQueryParam = \case
PDraft -> "draft"
PLive -> "live"
instance FromJSON PagesListStatus where
parseJSON = parseJSONText "PagesListStatus"
instance ToJSON PagesListStatus where
toJSON = toJSONText
data BlogsListByUserRole
= BLBURAdmin
| BLBURAuthor
| BLBURReader
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable BlogsListByUserRole
instance FromHttpApiData BlogsListByUserRole where
parseQueryParam = \case
"ADMIN" -> Right BLBURAdmin
"AUTHOR" -> Right BLBURAuthor
"READER" -> Right BLBURReader
x -> Left ("Unable to parse BlogsListByUserRole from: " <> x)
instance ToHttpApiData BlogsListByUserRole where
toQueryParam = \case
BLBURAdmin -> "ADMIN"
BLBURAuthor -> "AUTHOR"
BLBURReader -> "READER"
instance FromJSON BlogsListByUserRole where
parseJSON = parseJSONText "BlogsListByUserRole"
instance ToJSON BlogsListByUserRole where
toJSON = toJSONText