google-server-api-0.4.0.0: Google APIs for server to server applications
Safe HaskellNone
LanguageHaskell2010

Google.Type

Description

Define basic data types.

Documentation

newtype FileId Source #

Constructors

FileId 

Fields

Instances

Instances details
Eq FileId Source # 
Instance details

Defined in Google.Type

Methods

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

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

Show FileId Source # 
Instance details

Defined in Google.Type

Generic FileId Source # 
Instance details

Defined in Google.Type

Associated Types

type Rep FileId :: Type -> Type #

Methods

from :: FileId -> Rep FileId x #

to :: Rep FileId x -> FileId #

ToJSON FileId Source # 
Instance details

Defined in Google.Type

FromJSON FileId Source # 
Instance details

Defined in Google.Type

ToHttpApiData FileId Source # 
Instance details

Defined in Google.Type

type Rep FileId Source # 
Instance details

Defined in Google.Type

type Rep FileId = D1 ('MetaData "FileId" "Google.Type" "google-server-api-0.4.0.0-5LoNc1ksuKtGiJ22xbIvgC" 'True) (C1 ('MetaCons "FileId" 'PrefixI 'True) (S1 ('MetaSel ('Just "fileId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype MediaType Source #

Constructors

MediaType 

Fields

Instances

Instances details
Eq MediaType Source # 
Instance details

Defined in Google.Type

Show MediaType Source # 
Instance details

Defined in Google.Type

Generic MediaType Source # 
Instance details

Defined in Google.Type

Associated Types

type Rep MediaType :: Type -> Type #

ToJSON MediaType Source # 
Instance details

Defined in Google.Type

FromJSON MediaType Source # 
Instance details

Defined in Google.Type

type Rep MediaType Source # 
Instance details

Defined in Google.Type

type Rep MediaType = D1 ('MetaData "MediaType" "Google.Type" "google-server-api-0.4.0.0-5LoNc1ksuKtGiJ22xbIvgC" 'True) (C1 ('MetaCons "MediaType" 'PrefixI 'True) (S1 ('MetaSel ('Just "mediaTypeName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype MediaContent Source #

Constructors

MediaContent 

Fields

Instances

Instances details
Eq MediaContent Source # 
Instance details

Defined in Google.Type

Show MediaContent Source # 
Instance details

Defined in Google.Type

Generic MediaContent Source # 
Instance details

Defined in Google.Type

Associated Types

type Rep MediaContent :: Type -> Type #

MimeUnrender Arbitrary MediaContent Source # 
Instance details

Defined in Google.Type

type Rep MediaContent Source # 
Instance details

Defined in Google.Type

type Rep MediaContent = D1 ('MetaData "MediaContent" "Google.Type" "google-server-api-0.4.0.0-5LoNc1ksuKtGiJ22xbIvgC" 'True) (C1 ('MetaCons "MediaContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "content") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

data Metadata Source #

Constructors

Metadata 

Instances

Instances details
Eq Metadata Source # 
Instance details

Defined in Google.Type

Show Metadata Source # 
Instance details

Defined in Google.Type

Generic Metadata Source # 
Instance details

Defined in Google.Type

Associated Types

type Rep Metadata :: Type -> Type #

Methods

from :: Metadata -> Rep Metadata x #

to :: Rep Metadata x -> Metadata #

ToJSON Metadata Source # 
Instance details

Defined in Google.Type

FromJSON Metadata Source # 
Instance details

Defined in Google.Type

type Rep Metadata Source # 
Instance details

Defined in Google.Type

type Rep Metadata = D1 ('MetaData "Metadata" "Google.Type" "google-server-api-0.4.0.0-5LoNc1ksuKtGiJ22xbIvgC" 'False) (C1 ('MetaCons "Metadata" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "mimeType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe MediaType)) :*: S1 ('MetaSel ('Just "parents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [FileId])))))

data Multipart Source #

Instances

Instances details
Accept Multipart Source # 
Instance details

Defined in Google.Type

MimeRender Multipart MultipartBody Source # 
Instance details

Defined in Google.Form

data ConversionFormat Source #

Instances

Instances details
Eq ConversionFormat Source # 
Instance details

Defined in Google.Type

Show ConversionFormat Source # 
Instance details

Defined in Google.Type

Generic ConversionFormat Source # 
Instance details

Defined in Google.Type

Associated Types

type Rep ConversionFormat :: Type -> Type #

ToHttpApiData ConversionFormat Source # 
Instance details

Defined in Google.Type

type Rep ConversionFormat Source # 
Instance details

Defined in Google.Type

type Rep ConversionFormat = D1 ('MetaData "ConversionFormat" "Google.Type" "google-server-api-0.4.0.0-5LoNc1ksuKtGiJ22xbIvgC" 'False) ((((C1 ('MetaCons "FormatHtml" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FormatHtmlZipped" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FormatPlainText" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FormatRichText" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "FormatOpenOfficeDoc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FormatPdf" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FormatMsWordDoc" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FormatEpub" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FormatMsExcel" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "FormatOpenOfficeSheet" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FormatCsv" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FormatTsv" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FormatJpeg" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "FormatPng" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FormatSvg" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FormatMsPowerPoint" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FormatMsOfficePresentation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FormatJson" 'PrefixI 'False) (U1 :: Type -> Type))))))

data SortKey Source #

Instances

Instances details
Eq SortKey Source # 
Instance details

Defined in Google.Type

Methods

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

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

Show SortKey Source # 
Instance details

Defined in Google.Type

Generic SortKey Source # 
Instance details

Defined in Google.Type

Associated Types

type Rep SortKey :: Type -> Type #

Methods

from :: SortKey -> Rep SortKey x #

to :: Rep SortKey x -> SortKey #

ToHttpApiData SortKey Source # 
Instance details

Defined in Google.Type

type Rep SortKey Source # 
Instance details

Defined in Google.Type

type Rep SortKey = D1 ('MetaData "SortKey" "Google.Type" "google-server-api-0.4.0.0-5LoNc1ksuKtGiJ22xbIvgC" 'False) (((C1 ('MetaCons "CreatedTime" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Folder" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ModifiedByMeTime" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ModifiedTime" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Name" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "NameNatural" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "QuotaBytesUsed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Recency" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SsharedWithMeTime" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Starred" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ViewedByMeTime" 'PrefixI 'False) (U1 :: Type -> Type)))))

newtype QueryString Source #

Constructors

QueryString 

Fields

Instances

Instances details
Eq QueryString Source # 
Instance details

Defined in Google.Type

Show QueryString Source # 
Instance details

Defined in Google.Type

Generic QueryString Source # 
Instance details

Defined in Google.Type

Associated Types

type Rep QueryString :: Type -> Type #

ToJSON QueryString Source # 
Instance details

Defined in Google.Type

FromJSON QueryString Source # 
Instance details

Defined in Google.Type

ToHttpApiData QueryString Source # 
Instance details

Defined in Google.Type

type Rep QueryString Source # 
Instance details

Defined in Google.Type

type Rep QueryString = D1 ('MetaData "QueryString" "Google.Type" "google-server-api-0.4.0.0-5LoNc1ksuKtGiJ22xbIvgC" 'True) (C1 ('MetaCons "QueryString" 'PrefixI 'True) (S1 ('MetaSel ('Just "queryString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data Order Source #

Constructors

Asc SortKey 
Desc SortKey 

Instances

Instances details
Eq Order Source # 
Instance details

Defined in Google.Type

Methods

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

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

Show Order Source # 
Instance details

Defined in Google.Type

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

Generic Order Source # 
Instance details

Defined in Google.Type

Associated Types

type Rep Order :: Type -> Type #

Methods

from :: Order -> Rep Order x #

to :: Rep Order x -> Order #

ToHttpApiData Order Source # 
Instance details

Defined in Google.Type

ToHttpApiData [Order] Source # 
Instance details

Defined in Google.Type

type Rep Order Source # 
Instance details

Defined in Google.Type

type Rep Order = D1 ('MetaData "Order" "Google.Type" "google-server-api-0.4.0.0-5LoNc1ksuKtGiJ22xbIvgC" 'False) (C1 ('MetaCons "Asc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SortKey)) :+: C1 ('MetaCons "Desc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SortKey)))

newtype LabelId Source #

Constructors

LabelId Text 

Instances

Instances details
Eq LabelId Source # 
Instance details

Defined in Google.Type

Methods

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

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

Show LabelId Source # 
Instance details

Defined in Google.Type

Generic LabelId Source # 
Instance details

Defined in Google.Type

Associated Types

type Rep LabelId :: Type -> Type #

Methods

from :: LabelId -> Rep LabelId x #

to :: Rep LabelId x -> LabelId #

ToHttpApiData LabelId Source # 
Instance details

Defined in Google.Type

ToHttpApiData [LabelId] Source # 
Instance details

Defined in Google.Type

type Rep LabelId Source # 
Instance details

Defined in Google.Type

type Rep LabelId = D1 ('MetaData "LabelId" "Google.Type" "google-server-api-0.4.0.0-5LoNc1ksuKtGiJ22xbIvgC" 'True) (C1 ('MetaCons "LabelId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))