github-0.29: Access to the GitHub API, v3.
Safe HaskellSafe-Inferred
LanguageHaskell2010

GitHub.Data.Actions.Cache

Documentation

data Cache Source #

Instances

Instances details
FromJSON Cache Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

Data Cache Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

Methods

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

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

toConstr :: Cache -> Constr #

dataTypeOf :: Cache -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Cache Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

Associated Types

type Rep Cache :: Type -> Type #

Methods

from :: Cache -> Rep Cache x #

to :: Rep Cache x -> Cache #

Show Cache Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

Methods

showsPrec :: Int -> Cache -> ShowS #

show :: Cache -> String #

showList :: [Cache] -> ShowS #

Eq Cache Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

Methods

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

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

Ord Cache Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

Methods

compare :: Cache -> Cache -> Ordering #

(<) :: Cache -> Cache -> Bool #

(<=) :: Cache -> Cache -> Bool #

(>) :: Cache -> Cache -> Bool #

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

max :: Cache -> Cache -> Cache #

min :: Cache -> Cache -> Cache #

FromJSON (WithTotalCount Cache) Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

type Rep Cache Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

type Rep Cache = D1 ('MetaData "Cache" "GitHub.Data.Actions.Cache" "github-0.29-8pCAynMhaqD8pNGAeWnyh4" 'False) (C1 ('MetaCons "Cache" 'PrefixI 'True) ((S1 ('MetaSel ('Just "cacheId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Id Cache)) :*: (S1 ('MetaSel ('Just "cacheRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "cacheKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :*: ((S1 ('MetaSel ('Just "cacheVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "cacheLastAccessedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime)) :*: (S1 ('MetaSel ('Just "cacheCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "cacheSizeInBytes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))))

data RepositoryCacheUsage Source #

Instances

Instances details
FromJSON RepositoryCacheUsage Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

Data RepositoryCacheUsage Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

Methods

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

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

toConstr :: RepositoryCacheUsage -> Constr #

dataTypeOf :: RepositoryCacheUsage -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic RepositoryCacheUsage Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

Associated Types

type Rep RepositoryCacheUsage :: Type -> Type #

Show RepositoryCacheUsage Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

Eq RepositoryCacheUsage Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

Ord RepositoryCacheUsage Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

FromJSON (WithTotalCount RepositoryCacheUsage) Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

type Rep RepositoryCacheUsage Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

type Rep RepositoryCacheUsage = D1 ('MetaData "RepositoryCacheUsage" "GitHub.Data.Actions.Cache" "github-0.29-8pCAynMhaqD8pNGAeWnyh4" 'False) (C1 ('MetaCons "RepositoryCacheUsage" 'PrefixI 'True) (S1 ('MetaSel ('Just "repositoryCacheUsageFullName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "repositoryCacheUsageActiveCachesSizeInBytes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "repositoryCacheUsageActiveCachesCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))))

data OrganizationCacheUsage Source #

Instances

Instances details
FromJSON OrganizationCacheUsage Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

Data OrganizationCacheUsage Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

Methods

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

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

toConstr :: OrganizationCacheUsage -> Constr #

dataTypeOf :: OrganizationCacheUsage -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic OrganizationCacheUsage Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

Associated Types

type Rep OrganizationCacheUsage :: Type -> Type #

Show OrganizationCacheUsage Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

Eq OrganizationCacheUsage Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

Ord OrganizationCacheUsage Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

type Rep OrganizationCacheUsage Source # 
Instance details

Defined in GitHub.Data.Actions.Cache

type Rep OrganizationCacheUsage = D1 ('MetaData "OrganizationCacheUsage" "GitHub.Data.Actions.Cache" "github-0.29-8pCAynMhaqD8pNGAeWnyh4" 'False) (C1 ('MetaCons "OrganizationCacheUsage" 'PrefixI 'True) (S1 ('MetaSel ('Just "organizationCacheUsageTotalActiveCachesSizeInBytes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "organizationCacheUsageTotalActiveCachesCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))