gogol-pagespeed-0.4.0: Google PageSpeed Insights SDK.

Copyright(c) 2015-2016 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay@gmail.com>
Stabilityauto-generated
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.Google.PageSpeed

Contents

Description

Analyzes the performance of a web page and provides tailored suggestions to make that page faster.

See: PageSpeed Insights API Reference

Synopsis

Service Configuration

pageSpeedService :: ServiceConfig Source #

Default request referring to version v5 of the PageSpeed Insights API. This contains the host and root path used as a starting point for constructing service requests.

API Declaration

type PageSpeedAPI = PagespeedAPIRunPagespeedResource Source #

Represents the entirety of the methods and resources available for the PageSpeed Insights API service.

Resources

pagespeedonline.pagespeedapi.runpagespeed

Types

LighthouseResultV5CategoryGroups

data LighthouseResultV5CategoryGroups Source #

Map of category groups in the LHR.

See: lighthouseResultV5CategoryGroups smart constructor.

Instances
Eq LighthouseResultV5CategoryGroups Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data LighthouseResultV5CategoryGroups Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: LighthouseResultV5CategoryGroups -> Constr #

dataTypeOf :: LighthouseResultV5CategoryGroups -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LighthouseResultV5CategoryGroups Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic LighthouseResultV5CategoryGroups Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Associated Types

type Rep LighthouseResultV5CategoryGroups :: Type -> Type #

ToJSON LighthouseResultV5CategoryGroups Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON LighthouseResultV5CategoryGroups Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5CategoryGroups Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5CategoryGroups = D1 (MetaData "LighthouseResultV5CategoryGroups" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" True) (C1 (MetaCons "LighthouseResultV5CategoryGroups'" PrefixI True) (S1 (MetaSel (Just "_lrvcgAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text LighthouseResultV5CategoryGroupsAdditional))))

lighthouseResultV5CategoryGroups Source #

Creates a value of LighthouseResultV5CategoryGroups with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lrvcgAddtional :: Lens' LighthouseResultV5CategoryGroups (HashMap Text LighthouseResultV5CategoryGroupsAdditional) Source #

A grouping contained in a category that groups similar audits together.

LighthouseResultV5RuntimeError

data LighthouseResultV5RuntimeError Source #

A top-level error message that, if present, indicates a serious enough problem that this Lighthouse result may need to be discarded.

See: lighthouseResultV5RuntimeError smart constructor.

Instances
Eq LighthouseResultV5RuntimeError Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data LighthouseResultV5RuntimeError Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: LighthouseResultV5RuntimeError -> Constr #

dataTypeOf :: LighthouseResultV5RuntimeError -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LighthouseResultV5RuntimeError Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic LighthouseResultV5RuntimeError Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Associated Types

type Rep LighthouseResultV5RuntimeError :: Type -> Type #

ToJSON LighthouseResultV5RuntimeError Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON LighthouseResultV5RuntimeError Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5RuntimeError Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5RuntimeError = D1 (MetaData "LighthouseResultV5RuntimeError" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" False) (C1 (MetaCons "LighthouseResultV5RuntimeError'" PrefixI True) (S1 (MetaSel (Just "_lrvreCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lrvreMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

lighthouseResultV5RuntimeError :: LighthouseResultV5RuntimeError Source #

Creates a value of LighthouseResultV5RuntimeError with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lrvreCode :: Lens' LighthouseResultV5RuntimeError (Maybe Text) Source #

The enumerated Lighthouse Error code.

lrvreMessage :: Lens' LighthouseResultV5RuntimeError (Maybe Text) Source #

A human readable message explaining the error code.

LighthouseAuditResultV5Details

data LighthouseAuditResultV5Details Source #

Freeform details section of the audit.

See: lighthouseAuditResultV5Details smart constructor.

Instances
Eq LighthouseAuditResultV5Details Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data LighthouseAuditResultV5Details Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: LighthouseAuditResultV5Details -> Constr #

dataTypeOf :: LighthouseAuditResultV5Details -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LighthouseAuditResultV5Details Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic LighthouseAuditResultV5Details Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Associated Types

type Rep LighthouseAuditResultV5Details :: Type -> Type #

ToJSON LighthouseAuditResultV5Details Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON LighthouseAuditResultV5Details Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseAuditResultV5Details Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseAuditResultV5Details = D1 (MetaData "LighthouseAuditResultV5Details" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" True) (C1 (MetaCons "LighthouseAuditResultV5Details'" PrefixI True) (S1 (MetaSel (Just "_larvdAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text JSONValue))))

lighthouseAuditResultV5Details Source #

Creates a value of LighthouseAuditResultV5Details with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

LighthouseResultV5ConfigSettings

data LighthouseResultV5ConfigSettings Source #

The configuration settings for this LHR.

See: lighthouseResultV5ConfigSettings smart constructor.

Instances
Eq LighthouseResultV5ConfigSettings Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data LighthouseResultV5ConfigSettings Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: LighthouseResultV5ConfigSettings -> Constr #

dataTypeOf :: LighthouseResultV5ConfigSettings -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LighthouseResultV5ConfigSettings Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic LighthouseResultV5ConfigSettings Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Associated Types

type Rep LighthouseResultV5ConfigSettings :: Type -> Type #

ToJSON LighthouseResultV5ConfigSettings Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON LighthouseResultV5ConfigSettings Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5ConfigSettings Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5ConfigSettings = D1 (MetaData "LighthouseResultV5ConfigSettings" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" False) (C1 (MetaCons "LighthouseResultV5ConfigSettings'" PrefixI True) (S1 (MetaSel (Just "_lrvcsLocale") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_lrvcsEmulatedFormFactor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lrvcsOnlyCategories") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe JSONValue)))))

lighthouseResultV5ConfigSettings :: LighthouseResultV5ConfigSettings Source #

Creates a value of LighthouseResultV5ConfigSettings with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lrvcsEmulatedFormFactor :: Lens' LighthouseResultV5ConfigSettings (Maybe Text) Source #

The form factor the emulation should use.

PagespeedAPIRunPagespeedStrategy

data PagespeedAPIRunPagespeedStrategy Source #

The analysis strategy (desktop or mobile) to use, and desktop is the default

Constructors

Desktop

desktop Fetch and analyze the URL for desktop browsers

Mobile

mobile Fetch and analyze the URL for mobile devices

Instances
Enum PagespeedAPIRunPagespeedStrategy Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

Eq PagespeedAPIRunPagespeedStrategy Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

Data PagespeedAPIRunPagespeedStrategy Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

Methods

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

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

toConstr :: PagespeedAPIRunPagespeedStrategy -> Constr #

dataTypeOf :: PagespeedAPIRunPagespeedStrategy -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PagespeedAPIRunPagespeedStrategy Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

Read PagespeedAPIRunPagespeedStrategy Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

Show PagespeedAPIRunPagespeedStrategy Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

Generic PagespeedAPIRunPagespeedStrategy Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

Associated Types

type Rep PagespeedAPIRunPagespeedStrategy :: Type -> Type #

Hashable PagespeedAPIRunPagespeedStrategy Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

ToJSON PagespeedAPIRunPagespeedStrategy Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

FromJSON PagespeedAPIRunPagespeedStrategy Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

FromHttpApiData PagespeedAPIRunPagespeedStrategy Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

ToHttpApiData PagespeedAPIRunPagespeedStrategy Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

type Rep PagespeedAPIRunPagespeedStrategy Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

type Rep PagespeedAPIRunPagespeedStrategy = D1 (MetaData "PagespeedAPIRunPagespeedStrategy" "Network.Google.PageSpeed.Types.Sum" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" False) (C1 (MetaCons "Desktop" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Mobile" PrefixI False) (U1 :: Type -> Type))

LighthouseResultV5Environment

data LighthouseResultV5Environment Source #

Environment settings that were used when making this LHR.

See: lighthouseResultV5Environment smart constructor.

Instances
Eq LighthouseResultV5Environment Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data LighthouseResultV5Environment Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: LighthouseResultV5Environment -> Constr #

dataTypeOf :: LighthouseResultV5Environment -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LighthouseResultV5Environment Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic LighthouseResultV5Environment Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Associated Types

type Rep LighthouseResultV5Environment :: Type -> Type #

ToJSON LighthouseResultV5Environment Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON LighthouseResultV5Environment Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5Environment Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5Environment = D1 (MetaData "LighthouseResultV5Environment" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" False) (C1 (MetaCons "LighthouseResultV5Environment'" PrefixI True) (S1 (MetaSel (Just "_lrveHostUserAgent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_lrveBenchmarkIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))) :*: S1 (MetaSel (Just "_lrveNetworkUserAgent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

lighthouseResultV5Environment :: LighthouseResultV5Environment Source #

Creates a value of LighthouseResultV5Environment with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lrveHostUserAgent :: Lens' LighthouseResultV5Environment (Maybe Text) Source #

The user agent string of the version of Chrome used.

lrveBenchmarkIndex :: Lens' LighthouseResultV5Environment (Maybe Double) Source #

The benchmark index number that indicates rough device class.

lrveNetworkUserAgent :: Lens' LighthouseResultV5Environment (Maybe Text) Source #

The user agent string that was sent over the network.

LighthouseResultV5CategoryGroupsAdditional

data LighthouseResultV5CategoryGroupsAdditional Source #

A grouping contained in a category that groups similar audits together.

See: lighthouseResultV5CategoryGroupsAdditional smart constructor.

Instances
Eq LighthouseResultV5CategoryGroupsAdditional Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data LighthouseResultV5CategoryGroupsAdditional Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: LighthouseResultV5CategoryGroupsAdditional -> Constr #

dataTypeOf :: LighthouseResultV5CategoryGroupsAdditional -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LighthouseResultV5CategoryGroupsAdditional Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic LighthouseResultV5CategoryGroupsAdditional Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

ToJSON LighthouseResultV5CategoryGroupsAdditional Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON LighthouseResultV5CategoryGroupsAdditional Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5CategoryGroupsAdditional Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5CategoryGroupsAdditional = D1 (MetaData "LighthouseResultV5CategoryGroupsAdditional" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" False) (C1 (MetaCons "LighthouseResultV5CategoryGroupsAdditional'" PrefixI True) (S1 (MetaSel (Just "_lrvcgaTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lrvcgaDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

lighthouseResultV5CategoryGroupsAdditional :: LighthouseResultV5CategoryGroupsAdditional Source #

Creates a value of LighthouseResultV5CategoryGroupsAdditional with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lrvcgaDescription :: Lens' LighthouseResultV5CategoryGroupsAdditional (Maybe Text) Source #

An optional human readable description of the category group.

LighthouseAuditResultV5

data LighthouseAuditResultV5 Source #

Instances
Eq LighthouseAuditResultV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data LighthouseAuditResultV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: LighthouseAuditResultV5 -> Constr #

dataTypeOf :: LighthouseAuditResultV5 -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LighthouseAuditResultV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic LighthouseAuditResultV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Associated Types

type Rep LighthouseAuditResultV5 :: Type -> Type #

ToJSON LighthouseAuditResultV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON LighthouseAuditResultV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseAuditResultV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

lighthouseAuditResultV5 :: LighthouseAuditResultV5 Source #

Creates a value of LighthouseAuditResultV5 with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

larvExplanation :: Lens' LighthouseAuditResultV5 (Maybe Text) Source #

An explanation of the errors in the audit.

larvScoreDisplayMode :: Lens' LighthouseAuditResultV5 (Maybe Text) Source #

The enumerated score display mode.

larvDisplayValue :: Lens' LighthouseAuditResultV5 (Maybe Text) Source #

The value that should be displayed on the UI for this audit.

larvTitle :: Lens' LighthouseAuditResultV5 (Maybe Text) Source #

The human readable title.

larvErrorMessage :: Lens' LighthouseAuditResultV5 (Maybe Text) Source #

An error message from a thrown error inside the audit.

larvDescription :: Lens' LighthouseAuditResultV5 (Maybe Text) Source #

The description of the audit.

PagespeedAPIPagespeedResponseV5

data PagespeedAPIPagespeedResponseV5 Source #

Instances
Eq PagespeedAPIPagespeedResponseV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data PagespeedAPIPagespeedResponseV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: PagespeedAPIPagespeedResponseV5 -> Constr #

dataTypeOf :: PagespeedAPIPagespeedResponseV5 -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PagespeedAPIPagespeedResponseV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic PagespeedAPIPagespeedResponseV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Associated Types

type Rep PagespeedAPIPagespeedResponseV5 :: Type -> Type #

ToJSON PagespeedAPIPagespeedResponseV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON PagespeedAPIPagespeedResponseV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep PagespeedAPIPagespeedResponseV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep PagespeedAPIPagespeedResponseV5 = D1 (MetaData "PagespeedAPIPagespeedResponseV5" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" False) (C1 (MetaCons "PagespeedAPIPagespeedResponseV5'" PrefixI True) (((S1 (MetaSel (Just "_paprvKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_paprvOriginLoadingExperience") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PagespeedAPILoadingExperienceV5))) :*: (S1 (MetaSel (Just "_paprvVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PagespeedAPIPagespeedResponseV5Version)) :*: S1 (MetaSel (Just "_paprvCaptchaResult") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_paprvId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_paprvLoadingExperience") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PagespeedAPILoadingExperienceV5))) :*: (S1 (MetaSel (Just "_paprvLighthouseResult") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LighthouseResultV5)) :*: S1 (MetaSel (Just "_paprvAnalysisUTCTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

paprvOriginLoadingExperience :: Lens' PagespeedAPIPagespeedResponseV5 (Maybe PagespeedAPILoadingExperienceV5) Source #

Metrics of the aggregated page loading experience of the origin

paprvVersion :: Lens' PagespeedAPIPagespeedResponseV5 (Maybe PagespeedAPIPagespeedResponseV5Version) Source #

The version of PageSpeed used to generate these results.

paprvId :: Lens' PagespeedAPIPagespeedResponseV5 (Maybe Text) Source #

Canonicalized and final URL for the document, after following page redirects (if any).

paprvLighthouseResult :: Lens' PagespeedAPIPagespeedResponseV5 (Maybe LighthouseResultV5) Source #

Lighthouse response for the audit url as an object.

PagespeedAPILoadingExperienceV5Metrics

data PagespeedAPILoadingExperienceV5Metrics Source #

Instances
Eq PagespeedAPILoadingExperienceV5Metrics Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data PagespeedAPILoadingExperienceV5Metrics Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: PagespeedAPILoadingExperienceV5Metrics -> Constr #

dataTypeOf :: PagespeedAPILoadingExperienceV5Metrics -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PagespeedAPILoadingExperienceV5Metrics Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic PagespeedAPILoadingExperienceV5Metrics Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

ToJSON PagespeedAPILoadingExperienceV5Metrics Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON PagespeedAPILoadingExperienceV5Metrics Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep PagespeedAPILoadingExperienceV5Metrics Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep PagespeedAPILoadingExperienceV5Metrics = D1 (MetaData "PagespeedAPILoadingExperienceV5Metrics" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" True) (C1 (MetaCons "PagespeedAPILoadingExperienceV5Metrics'" PrefixI True) (S1 (MetaSel (Just "_palevmAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text PagespeedAPILoadingExperienceV5MetricsAdditional))))

pagespeedAPILoadingExperienceV5Metrics Source #

Creates a value of PagespeedAPILoadingExperienceV5Metrics with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

LighthouseResultV5

data LighthouseResultV5 Source #

Instances
Eq LighthouseResultV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data LighthouseResultV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: LighthouseResultV5 -> Constr #

dataTypeOf :: LighthouseResultV5 -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LighthouseResultV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic LighthouseResultV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Associated Types

type Rep LighthouseResultV5 :: Type -> Type #

ToJSON LighthouseResultV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON LighthouseResultV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5 = D1 (MetaData "LighthouseResultV5" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" False) (C1 (MetaCons "LighthouseResultV5'" PrefixI True) (((S1 (MetaSel (Just "_lrvRuntimeError") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LighthouseResultV5RuntimeError)) :*: (S1 (MetaSel (Just "_lrvCategoryGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LighthouseResultV5CategoryGroups)) :*: S1 (MetaSel (Just "_lrvFinalURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_lrvConfigSettings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LighthouseResultV5ConfigSettings)) :*: S1 (MetaSel (Just "_lrvEnvironment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LighthouseResultV5Environment))) :*: (S1 (MetaSel (Just "_lrvLighthouseVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lrvRunWarnings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [JSONValue]))))) :*: ((S1 (MetaSel (Just "_lrvRequestedURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_lrvCategories") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LighthouseResultV5Categories)) :*: S1 (MetaSel (Just "_lrvFetchTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_lrvUserAgent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lrvTiming") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LighthouseResultV5Timing))) :*: (S1 (MetaSel (Just "_lrvAudits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LighthouseResultV5Audits)) :*: S1 (MetaSel (Just "_lrvI18n") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LighthouseResultV5I18n)))))))

lrvRuntimeError :: Lens' LighthouseResultV5 (Maybe LighthouseResultV5RuntimeError) Source #

A top-level error message that, if present, indicates a serious enough problem that this Lighthouse result may need to be discarded.

lrvFinalURL :: Lens' LighthouseResultV5 (Maybe Text) Source #

The final resolved url that was audited.

lrvEnvironment :: Lens' LighthouseResultV5 (Maybe LighthouseResultV5Environment) Source #

Environment settings that were used when making this LHR.

lrvLighthouseVersion :: Lens' LighthouseResultV5 (Maybe Text) Source #

The lighthouse version that was used to generate this LHR.

lrvRunWarnings :: Lens' LighthouseResultV5 [JSONValue] Source #

List of all run warnings in the LHR. Will always output to at least `[]`.

lrvRequestedURL :: Lens' LighthouseResultV5 (Maybe Text) Source #

The original requested url.

lrvFetchTime :: Lens' LighthouseResultV5 (Maybe Text) Source #

The time that this run was fetched.

lrvUserAgent :: Lens' LighthouseResultV5 (Maybe Text) Source #

The user agent that was used to run this LHR.

lrvI18n :: Lens' LighthouseResultV5 (Maybe LighthouseResultV5I18n) Source #

The internationalization strings that are required to render the LHR.

LighthouseResultV5Categories

data LighthouseResultV5Categories Source #

Map of categories in the LHR.

See: lighthouseResultV5Categories smart constructor.

Instances
Eq LighthouseResultV5Categories Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data LighthouseResultV5Categories Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: LighthouseResultV5Categories -> Constr #

dataTypeOf :: LighthouseResultV5Categories -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LighthouseResultV5Categories Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic LighthouseResultV5Categories Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Associated Types

type Rep LighthouseResultV5Categories :: Type -> Type #

ToJSON LighthouseResultV5Categories Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON LighthouseResultV5Categories Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5Categories Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5Categories = D1 (MetaData "LighthouseResultV5Categories" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" False) (C1 (MetaCons "LighthouseResultV5Categories'" PrefixI True) ((S1 (MetaSel (Just "_lrvcBestPractices") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LighthouseCategoryV5)) :*: S1 (MetaSel (Just "_lrvcPerformance") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LighthouseCategoryV5))) :*: (S1 (MetaSel (Just "_lrvcPwa") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LighthouseCategoryV5)) :*: (S1 (MetaSel (Just "_lrvcSeo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LighthouseCategoryV5)) :*: S1 (MetaSel (Just "_lrvcAccessibility") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LighthouseCategoryV5))))))

lighthouseResultV5Categories :: LighthouseResultV5Categories Source #

Creates a value of LighthouseResultV5Categories with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lrvcBestPractices :: Lens' LighthouseResultV5Categories (Maybe LighthouseCategoryV5) Source #

The best practices category, containing all web best practice related audits.

lrvcPerformance :: Lens' LighthouseResultV5Categories (Maybe LighthouseCategoryV5) Source #

The performance category, containing all performance related audits.

lrvcPwa :: Lens' LighthouseResultV5Categories (Maybe LighthouseCategoryV5) Source #

The Progressive-Web-App (PWA) category, containing all pwa related audits.

lrvcSeo :: Lens' LighthouseResultV5Categories (Maybe LighthouseCategoryV5) Source #

The Search-Engine-Optimization (SEO) category, containing all seo related audits.

lrvcAccessibility :: Lens' LighthouseResultV5Categories (Maybe LighthouseCategoryV5) Source #

The accessibility category, containing all accessibility related audits.

PagespeedAPIRunPagespeedCategory

data PagespeedAPIRunPagespeedCategory Source #

A Lighthouse category to run; if none are given, only Performance category will be run

Constructors

Accessibility
accessibility
BestPractices
best-practices
Performance
performance
Pwa
pwa
Seo
seo
Instances
Enum PagespeedAPIRunPagespeedCategory Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

Eq PagespeedAPIRunPagespeedCategory Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

Data PagespeedAPIRunPagespeedCategory Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

Methods

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

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

toConstr :: PagespeedAPIRunPagespeedCategory -> Constr #

dataTypeOf :: PagespeedAPIRunPagespeedCategory -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PagespeedAPIRunPagespeedCategory Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

Read PagespeedAPIRunPagespeedCategory Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

Show PagespeedAPIRunPagespeedCategory Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

Generic PagespeedAPIRunPagespeedCategory Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

Associated Types

type Rep PagespeedAPIRunPagespeedCategory :: Type -> Type #

Hashable PagespeedAPIRunPagespeedCategory Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

ToJSON PagespeedAPIRunPagespeedCategory Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

FromJSON PagespeedAPIRunPagespeedCategory Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

FromHttpApiData PagespeedAPIRunPagespeedCategory Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

ToHttpApiData PagespeedAPIRunPagespeedCategory Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

type Rep PagespeedAPIRunPagespeedCategory Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Sum

type Rep PagespeedAPIRunPagespeedCategory = D1 (MetaData "PagespeedAPIRunPagespeedCategory" "Network.Google.PageSpeed.Types.Sum" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" False) ((C1 (MetaCons "Accessibility" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BestPractices" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Performance" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Pwa" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Seo" PrefixI False) (U1 :: Type -> Type))))

LighthouseCategoryV5

data LighthouseCategoryV5 Source #

Instances
Eq LighthouseCategoryV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data LighthouseCategoryV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: LighthouseCategoryV5 -> Constr #

dataTypeOf :: LighthouseCategoryV5 -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LighthouseCategoryV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic LighthouseCategoryV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Associated Types

type Rep LighthouseCategoryV5 :: Type -> Type #

ToJSON LighthouseCategoryV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON LighthouseCategoryV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseCategoryV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseCategoryV5 = D1 (MetaData "LighthouseCategoryV5" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" False) (C1 (MetaCons "LighthouseCategoryV5'" PrefixI True) ((S1 (MetaSel (Just "_lcvManualDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_lcvScore") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe JSONValue)) :*: S1 (MetaSel (Just "_lcvAuditRefs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [LighthouseCategoryV5AuditRefsItem])))) :*: (S1 (MetaSel (Just "_lcvId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_lcvTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lcvDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

lighthouseCategoryV5 :: LighthouseCategoryV5 Source #

Creates a value of LighthouseCategoryV5 with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lcvManualDescription :: Lens' LighthouseCategoryV5 (Maybe Text) Source #

A description for the manual audits in the category.

lcvAuditRefs :: Lens' LighthouseCategoryV5 [LighthouseCategoryV5AuditRefsItem] Source #

An array of references to all the audit members of this category.

lcvId :: Lens' LighthouseCategoryV5 (Maybe Text) Source #

The string identifier of the category.

lcvTitle :: Lens' LighthouseCategoryV5 (Maybe Text) Source #

The human-friendly name of the category.

lcvDescription :: Lens' LighthouseCategoryV5 (Maybe Text) Source #

A more detailed description of the category and its importance.

PagespeedAPILoadingExperienceV5MetricsAdditional

data PagespeedAPILoadingExperienceV5MetricsAdditional Source #

The type of the metric.

See: pagespeedAPILoadingExperienceV5MetricsAdditional smart constructor.

Instances
Eq PagespeedAPILoadingExperienceV5MetricsAdditional Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data PagespeedAPILoadingExperienceV5MetricsAdditional Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: PagespeedAPILoadingExperienceV5MetricsAdditional -> Constr #

dataTypeOf :: PagespeedAPILoadingExperienceV5MetricsAdditional -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PagespeedAPILoadingExperienceV5MetricsAdditional Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic PagespeedAPILoadingExperienceV5MetricsAdditional Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

ToJSON PagespeedAPILoadingExperienceV5MetricsAdditional Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON PagespeedAPILoadingExperienceV5MetricsAdditional Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep PagespeedAPILoadingExperienceV5MetricsAdditional Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep PagespeedAPILoadingExperienceV5MetricsAdditional = D1 (MetaData "PagespeedAPILoadingExperienceV5MetricsAdditional" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" False) (C1 (MetaCons "PagespeedAPILoadingExperienceV5MetricsAdditional'" PrefixI True) (S1 (MetaSel (Just "_palevmaCategory") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_palevmaPercentile") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_palevmaDistributions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [PagespeedAPILoadingExperienceV5MetricsAdditionalDistributionsItem])))))

pagespeedAPILoadingExperienceV5MetricsAdditional :: PagespeedAPILoadingExperienceV5MetricsAdditional Source #

Creates a value of PagespeedAPILoadingExperienceV5MetricsAdditional with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

PagespeedAPILoadingExperienceV5

data PagespeedAPILoadingExperienceV5 Source #

Instances
Eq PagespeedAPILoadingExperienceV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data PagespeedAPILoadingExperienceV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: PagespeedAPILoadingExperienceV5 -> Constr #

dataTypeOf :: PagespeedAPILoadingExperienceV5 -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PagespeedAPILoadingExperienceV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic PagespeedAPILoadingExperienceV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Associated Types

type Rep PagespeedAPILoadingExperienceV5 :: Type -> Type #

ToJSON PagespeedAPILoadingExperienceV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON PagespeedAPILoadingExperienceV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep PagespeedAPILoadingExperienceV5 Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep PagespeedAPILoadingExperienceV5 = D1 (MetaData "PagespeedAPILoadingExperienceV5" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" False) (C1 (MetaCons "PagespeedAPILoadingExperienceV5'" PrefixI True) ((S1 (MetaSel (Just "_palevMetrics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PagespeedAPILoadingExperienceV5Metrics)) :*: S1 (MetaSel (Just "_palevInitialURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_palevId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_palevOverallCategory") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

pagespeedAPILoadingExperienceV5 :: PagespeedAPILoadingExperienceV5 Source #

Creates a value of PagespeedAPILoadingExperienceV5 with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

palevId :: Lens' PagespeedAPILoadingExperienceV5 (Maybe Text) Source #

The url, pattern or origin which the metrics are on.

PagespeedAPIPagespeedResponseV5Version

data PagespeedAPIPagespeedResponseV5Version Source #

The version of PageSpeed used to generate these results.

See: pagespeedAPIPagespeedResponseV5Version smart constructor.

Instances
Eq PagespeedAPIPagespeedResponseV5Version Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data PagespeedAPIPagespeedResponseV5Version Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: PagespeedAPIPagespeedResponseV5Version -> Constr #

dataTypeOf :: PagespeedAPIPagespeedResponseV5Version -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PagespeedAPIPagespeedResponseV5Version Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic PagespeedAPIPagespeedResponseV5Version Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

ToJSON PagespeedAPIPagespeedResponseV5Version Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON PagespeedAPIPagespeedResponseV5Version Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep PagespeedAPIPagespeedResponseV5Version Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep PagespeedAPIPagespeedResponseV5Version = D1 (MetaData "PagespeedAPIPagespeedResponseV5Version" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" False) (C1 (MetaCons "PagespeedAPIPagespeedResponseV5Version'" PrefixI True) (S1 (MetaSel (Just "_paprvvMinor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_paprvvMajor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))))

pagespeedAPIPagespeedResponseV5Version :: PagespeedAPIPagespeedResponseV5Version Source #

Creates a value of PagespeedAPIPagespeedResponseV5Version with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

paprvvMinor :: Lens' PagespeedAPIPagespeedResponseV5Version (Maybe Int32) Source #

The minor version number of PageSpeed used to generate these results.

paprvvMajor :: Lens' PagespeedAPIPagespeedResponseV5Version (Maybe Int32) Source #

The major version number of PageSpeed used to generate these results.

PagespeedAPILoadingExperienceV5MetricsAdditionalDistributionsItem

data PagespeedAPILoadingExperienceV5MetricsAdditionalDistributionsItem Source #

Instances
Eq PagespeedAPILoadingExperienceV5MetricsAdditionalDistributionsItem Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data PagespeedAPILoadingExperienceV5MetricsAdditionalDistributionsItem Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: PagespeedAPILoadingExperienceV5MetricsAdditionalDistributionsItem -> Constr #

dataTypeOf :: PagespeedAPILoadingExperienceV5MetricsAdditionalDistributionsItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PagespeedAPILoadingExperienceV5MetricsAdditionalDistributionsItem Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic PagespeedAPILoadingExperienceV5MetricsAdditionalDistributionsItem Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

ToJSON PagespeedAPILoadingExperienceV5MetricsAdditionalDistributionsItem Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON PagespeedAPILoadingExperienceV5MetricsAdditionalDistributionsItem Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep PagespeedAPILoadingExperienceV5MetricsAdditionalDistributionsItem Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep PagespeedAPILoadingExperienceV5MetricsAdditionalDistributionsItem = D1 (MetaData "PagespeedAPILoadingExperienceV5MetricsAdditionalDistributionsItem" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" False) (C1 (MetaCons "PagespeedAPILoadingExperienceV5MetricsAdditionalDistributionsItem'" PrefixI True) (S1 (MetaSel (Just "_palevmadiMax") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: (S1 (MetaSel (Just "_palevmadiProportion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))) :*: S1 (MetaSel (Just "_palevmadiMin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))

LighthouseResultV5Timing

data LighthouseResultV5Timing Source #

Timing information for this LHR.

See: lighthouseResultV5Timing smart constructor.

Instances
Eq LighthouseResultV5Timing Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data LighthouseResultV5Timing Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: LighthouseResultV5Timing -> Constr #

dataTypeOf :: LighthouseResultV5Timing -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LighthouseResultV5Timing Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic LighthouseResultV5Timing Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Associated Types

type Rep LighthouseResultV5Timing :: Type -> Type #

ToJSON LighthouseResultV5Timing Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON LighthouseResultV5Timing Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5Timing Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5Timing = D1 (MetaData "LighthouseResultV5Timing" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" True) (C1 (MetaCons "LighthouseResultV5Timing'" PrefixI True) (S1 (MetaSel (Just "_lrvtTotal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Textual Double)))))

lighthouseResultV5Timing :: LighthouseResultV5Timing Source #

Creates a value of LighthouseResultV5Timing with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lrvtTotal :: Lens' LighthouseResultV5Timing (Maybe Double) Source #

The total duration of Lighthouse's run.

LighthouseResultV5I18nRendererFormattedStrings

data LighthouseResultV5I18nRendererFormattedStrings Source #

Internationalized strings that are formatted to the locale in configSettings.

See: lighthouseResultV5I18nRendererFormattedStrings smart constructor.

Instances
Eq LighthouseResultV5I18nRendererFormattedStrings Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data LighthouseResultV5I18nRendererFormattedStrings Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: LighthouseResultV5I18nRendererFormattedStrings -> Constr #

dataTypeOf :: LighthouseResultV5I18nRendererFormattedStrings -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LighthouseResultV5I18nRendererFormattedStrings Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic LighthouseResultV5I18nRendererFormattedStrings Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

ToJSON LighthouseResultV5I18nRendererFormattedStrings Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON LighthouseResultV5I18nRendererFormattedStrings Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5I18nRendererFormattedStrings Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5I18nRendererFormattedStrings = D1 (MetaData "LighthouseResultV5I18nRendererFormattedStrings" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" False) (C1 (MetaCons "LighthouseResultV5I18nRendererFormattedStrings'" PrefixI True) ((((S1 (MetaSel (Just "_lrvirfsLabDataTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lrvirfsWarningHeader") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_lrvirfsOpportUnityResourceColumnLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lrvirfsManualAuditsGroupTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_lrvirfsCrcInitialNavigation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lrvirfsVarianceDisclaimer") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_lrvirfsPassedAuditsGroupTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lrvirfsToplevelWarningsMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) :*: (((S1 (MetaSel (Just "_lrvirfsErrorMissingAuditInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lrvirfsCrcLongestDurationLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_lrvirfsScorescaleLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lrvirfsOpportUnitySavingsColumnLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_lrvirfsErrorLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lrvirfsLsPerformanceCategoryDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_lrvirfsAuditGroupExpandTooltip") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lrvirfsNotApplicableAuditsGroupTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

lrvirfsLabDataTitle :: Lens' LighthouseResultV5I18nRendererFormattedStrings (Maybe Text) Source #

The title of the lab data performance category.

lrvirfsWarningHeader :: Lens' LighthouseResultV5I18nRendererFormattedStrings (Maybe Text) Source #

The label shown above a bulleted list of warnings.

lrvirfsOpportUnityResourceColumnLabel :: Lens' LighthouseResultV5I18nRendererFormattedStrings (Maybe Text) Source #

The heading for the estimated page load savings opportunity of an audit.

lrvirfsManualAuditsGroupTitle :: Lens' LighthouseResultV5I18nRendererFormattedStrings (Maybe Text) Source #

The heading shown above a list of audits that were not computerd in the run.

lrvirfsCrcInitialNavigation :: Lens' LighthouseResultV5I18nRendererFormattedStrings (Maybe Text) Source #

The label for the initial request in a critical request chain.

lrvirfsVarianceDisclaimer :: Lens' LighthouseResultV5I18nRendererFormattedStrings (Maybe Text) Source #

The disclaimer shown below a performance metric value.

lrvirfsPassedAuditsGroupTitle :: Lens' LighthouseResultV5I18nRendererFormattedStrings (Maybe Text) Source #

The heading that is shown above a list of audits that are passing.

lrvirfsToplevelWarningsMessage :: Lens' LighthouseResultV5I18nRendererFormattedStrings (Maybe Text) Source #

The label shown preceding important warnings that may have invalidated an entire report.

lrvirfsCrcLongestDurationLabel :: Lens' LighthouseResultV5I18nRendererFormattedStrings (Maybe Text) Source #

The label for values shown in the summary of critical request chains.

lrvirfsScorescaleLabel :: Lens' LighthouseResultV5I18nRendererFormattedStrings (Maybe Text) Source #

The label that explains the score gauges scale (0-49, 50-89, 90-100).

lrvirfsOpportUnitySavingsColumnLabel :: Lens' LighthouseResultV5I18nRendererFormattedStrings (Maybe Text) Source #

The heading for the estimated page load savings of opportunity audits.

lrvirfsErrorLabel :: Lens' LighthouseResultV5I18nRendererFormattedStrings (Maybe Text) Source #

The label shown next to an audit or metric that has had an error.

lrvirfsLsPerformanceCategoryDescription :: Lens' LighthouseResultV5I18nRendererFormattedStrings (Maybe Text) Source #

The disclaimer shown under performance explaning that the network can vary.

lrvirfsNotApplicableAuditsGroupTitle :: Lens' LighthouseResultV5I18nRendererFormattedStrings (Maybe Text) Source #

The heading shown above a list of audits that do not apply to a page.

LighthouseCategoryV5AuditRefsItem

data LighthouseCategoryV5AuditRefsItem Source #

Instances
Eq LighthouseCategoryV5AuditRefsItem Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data LighthouseCategoryV5AuditRefsItem Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: LighthouseCategoryV5AuditRefsItem -> Constr #

dataTypeOf :: LighthouseCategoryV5AuditRefsItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LighthouseCategoryV5AuditRefsItem Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic LighthouseCategoryV5AuditRefsItem Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Associated Types

type Rep LighthouseCategoryV5AuditRefsItem :: Type -> Type #

ToJSON LighthouseCategoryV5AuditRefsItem Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON LighthouseCategoryV5AuditRefsItem Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseCategoryV5AuditRefsItem Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseCategoryV5AuditRefsItem = D1 (MetaData "LighthouseCategoryV5AuditRefsItem" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" False) (C1 (MetaCons "LighthouseCategoryV5AuditRefsItem'" PrefixI True) (S1 (MetaSel (Just "_lcvariGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_lcvariWeight") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))) :*: S1 (MetaSel (Just "_lcvariId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

lighthouseCategoryV5AuditRefsItem :: LighthouseCategoryV5AuditRefsItem Source #

Creates a value of LighthouseCategoryV5AuditRefsItem with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lcvariGroup :: Lens' LighthouseCategoryV5AuditRefsItem (Maybe Text) Source #

The category group that the audit belongs to (optional).

lcvariWeight :: Lens' LighthouseCategoryV5AuditRefsItem (Maybe Double) Source #

The weight this audit's score has on the overall category score.

LighthouseResultV5I18n

data LighthouseResultV5I18n Source #

The internationalization strings that are required to render the LHR.

See: lighthouseResultV5I18n smart constructor.

Instances
Eq LighthouseResultV5I18n Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data LighthouseResultV5I18n Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: LighthouseResultV5I18n -> Constr #

dataTypeOf :: LighthouseResultV5I18n -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LighthouseResultV5I18n Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic LighthouseResultV5I18n Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Associated Types

type Rep LighthouseResultV5I18n :: Type -> Type #

ToJSON LighthouseResultV5I18n Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON LighthouseResultV5I18n Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5I18n Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5I18n = D1 (MetaData "LighthouseResultV5I18n" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" True) (C1 (MetaCons "LighthouseResultV5I18n'" PrefixI True) (S1 (MetaSel (Just "_lrviRendererFormattedStrings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LighthouseResultV5I18nRendererFormattedStrings))))

lighthouseResultV5I18n :: LighthouseResultV5I18n Source #

Creates a value of LighthouseResultV5I18n with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lrviRendererFormattedStrings :: Lens' LighthouseResultV5I18n (Maybe LighthouseResultV5I18nRendererFormattedStrings) Source #

Internationalized strings that are formatted to the locale in configSettings.

LighthouseResultV5Audits

data LighthouseResultV5Audits Source #

Map of audits in the LHR.

See: lighthouseResultV5Audits smart constructor.

Instances
Eq LighthouseResultV5Audits Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Data LighthouseResultV5Audits Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Methods

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

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

toConstr :: LighthouseResultV5Audits -> Constr #

dataTypeOf :: LighthouseResultV5Audits -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LighthouseResultV5Audits Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Generic LighthouseResultV5Audits Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

Associated Types

type Rep LighthouseResultV5Audits :: Type -> Type #

ToJSON LighthouseResultV5Audits Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

FromJSON LighthouseResultV5Audits Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5Audits Source # 
Instance details

Defined in Network.Google.PageSpeed.Types.Product

type Rep LighthouseResultV5Audits = D1 (MetaData "LighthouseResultV5Audits" "Network.Google.PageSpeed.Types.Product" "gogol-pagespeed-0.4.0-7WtThApEGYk4TnkQhzuhcc" True) (C1 (MetaCons "LighthouseResultV5Audits'" PrefixI True) (S1 (MetaSel (Just "_lrvaAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text LighthouseAuditResultV5))))

lighthouseResultV5Audits Source #

Creates a value of LighthouseResultV5Audits with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lrvaAddtional :: Lens' LighthouseResultV5Audits (HashMap Text LighthouseAuditResultV5) Source #

An audit that was performed in this run. Keyed by audit id.