{-# LANGUAGE DataKinds         #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures    #-}

module GitHub.Data.Actions.Cache (
    Cache(..),
    RepositoryCacheUsage(..),
    OrganizationCacheUsage(..)
    ) where

import GitHub.Data.Id          (Id)
import GitHub.Internal.Prelude
import Prelude ()

import GitHub.Data.Actions.Common (WithTotalCount (WithTotalCount))

-------------------------------------------------------------------------------
-- Cache
-------------------------------------------------------------------------------

data Cache = Cache
    { Cache -> Id Cache
cacheId             :: !(Id Cache)
    , Cache -> Text
cacheRef            :: !Text
    , Cache -> Text
cacheKey            :: !Text
    , Cache -> Text
cacheVersion        :: !Text
    , Cache -> UTCTime
cacheLastAccessedAt :: !UTCTime
    , Cache -> UTCTime
cacheCreatedAt      :: !UTCTime
    , Cache -> Int
cacheSizeInBytes    :: !Int
    }
  deriving (Int -> Cache -> ShowS
[Cache] -> ShowS
Cache -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Cache] -> ShowS
$cshowList :: [Cache] -> ShowS
show :: Cache -> String
$cshow :: Cache -> String
showsPrec :: Int -> Cache -> ShowS
$cshowsPrec :: Int -> Cache -> ShowS
Show, Typeable Cache
Cache -> DataType
Cache -> Constr
(forall b. Data b => b -> b) -> Cache -> Cache
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Cache -> u
forall u. (forall d. Data d => d -> u) -> Cache -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cache -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cache -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Cache -> m Cache
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cache -> m Cache
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Cache
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Cache -> c Cache
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Cache)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cache)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cache -> m Cache
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cache -> m Cache
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cache -> m Cache
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cache -> m Cache
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Cache -> m Cache
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Cache -> m Cache
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Cache -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Cache -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Cache -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Cache -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cache -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cache -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cache -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cache -> r
gmapT :: (forall b. Data b => b -> b) -> Cache -> Cache
$cgmapT :: (forall b. Data b => b -> b) -> Cache -> Cache
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cache)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cache)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Cache)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Cache)
dataTypeOf :: Cache -> DataType
$cdataTypeOf :: Cache -> DataType
toConstr :: Cache -> Constr
$ctoConstr :: Cache -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Cache
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Cache
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Cache -> c Cache
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Cache -> c Cache
Data, Typeable, Cache -> Cache -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cache -> Cache -> Bool
$c/= :: Cache -> Cache -> Bool
== :: Cache -> Cache -> Bool
$c== :: Cache -> Cache -> Bool
Eq, Eq Cache
Cache -> Cache -> Bool
Cache -> Cache -> Ordering
Cache -> Cache -> Cache
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Cache -> Cache -> Cache
$cmin :: Cache -> Cache -> Cache
max :: Cache -> Cache -> Cache
$cmax :: Cache -> Cache -> Cache
>= :: Cache -> Cache -> Bool
$c>= :: Cache -> Cache -> Bool
> :: Cache -> Cache -> Bool
$c> :: Cache -> Cache -> Bool
<= :: Cache -> Cache -> Bool
$c<= :: Cache -> Cache -> Bool
< :: Cache -> Cache -> Bool
$c< :: Cache -> Cache -> Bool
compare :: Cache -> Cache -> Ordering
$ccompare :: Cache -> Cache -> Ordering
Ord, forall x. Rep Cache x -> Cache
forall x. Cache -> Rep Cache x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Cache x -> Cache
$cfrom :: forall x. Cache -> Rep Cache x
Generic)

data RepositoryCacheUsage = RepositoryCacheUsage
    { RepositoryCacheUsage -> Text
repositoryCacheUsageFullName                :: !Text
    , RepositoryCacheUsage -> Int
repositoryCacheUsageActiveCachesSizeInBytes :: !Int
    , RepositoryCacheUsage -> Int
repositoryCacheUsageActiveCachesCount       :: !Int
    }
  deriving (Int -> RepositoryCacheUsage -> ShowS
[RepositoryCacheUsage] -> ShowS
RepositoryCacheUsage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RepositoryCacheUsage] -> ShowS
$cshowList :: [RepositoryCacheUsage] -> ShowS
show :: RepositoryCacheUsage -> String
$cshow :: RepositoryCacheUsage -> String
showsPrec :: Int -> RepositoryCacheUsage -> ShowS
$cshowsPrec :: Int -> RepositoryCacheUsage -> ShowS
Show, Typeable RepositoryCacheUsage
RepositoryCacheUsage -> DataType
RepositoryCacheUsage -> Constr
(forall b. Data b => b -> b)
-> RepositoryCacheUsage -> RepositoryCacheUsage
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> RepositoryCacheUsage -> u
forall u.
(forall d. Data d => d -> u) -> RepositoryCacheUsage -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepositoryCacheUsage -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepositoryCacheUsage -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RepositoryCacheUsage -> m RepositoryCacheUsage
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RepositoryCacheUsage -> m RepositoryCacheUsage
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepositoryCacheUsage
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RepositoryCacheUsage
-> c RepositoryCacheUsage
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepositoryCacheUsage)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RepositoryCacheUsage)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RepositoryCacheUsage -> m RepositoryCacheUsage
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RepositoryCacheUsage -> m RepositoryCacheUsage
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RepositoryCacheUsage -> m RepositoryCacheUsage
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RepositoryCacheUsage -> m RepositoryCacheUsage
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RepositoryCacheUsage -> m RepositoryCacheUsage
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RepositoryCacheUsage -> m RepositoryCacheUsage
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> RepositoryCacheUsage -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> RepositoryCacheUsage -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> RepositoryCacheUsage -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> RepositoryCacheUsage -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepositoryCacheUsage -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepositoryCacheUsage -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepositoryCacheUsage -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepositoryCacheUsage -> r
gmapT :: (forall b. Data b => b -> b)
-> RepositoryCacheUsage -> RepositoryCacheUsage
$cgmapT :: (forall b. Data b => b -> b)
-> RepositoryCacheUsage -> RepositoryCacheUsage
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RepositoryCacheUsage)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RepositoryCacheUsage)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepositoryCacheUsage)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepositoryCacheUsage)
dataTypeOf :: RepositoryCacheUsage -> DataType
$cdataTypeOf :: RepositoryCacheUsage -> DataType
toConstr :: RepositoryCacheUsage -> Constr
$ctoConstr :: RepositoryCacheUsage -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepositoryCacheUsage
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepositoryCacheUsage
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RepositoryCacheUsage
-> c RepositoryCacheUsage
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RepositoryCacheUsage
-> c RepositoryCacheUsage
Data, Typeable, RepositoryCacheUsage -> RepositoryCacheUsage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RepositoryCacheUsage -> RepositoryCacheUsage -> Bool
$c/= :: RepositoryCacheUsage -> RepositoryCacheUsage -> Bool
== :: RepositoryCacheUsage -> RepositoryCacheUsage -> Bool
$c== :: RepositoryCacheUsage -> RepositoryCacheUsage -> Bool
Eq, Eq RepositoryCacheUsage
RepositoryCacheUsage -> RepositoryCacheUsage -> Bool
RepositoryCacheUsage -> RepositoryCacheUsage -> Ordering
RepositoryCacheUsage
-> RepositoryCacheUsage -> RepositoryCacheUsage
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RepositoryCacheUsage
-> RepositoryCacheUsage -> RepositoryCacheUsage
$cmin :: RepositoryCacheUsage
-> RepositoryCacheUsage -> RepositoryCacheUsage
max :: RepositoryCacheUsage
-> RepositoryCacheUsage -> RepositoryCacheUsage
$cmax :: RepositoryCacheUsage
-> RepositoryCacheUsage -> RepositoryCacheUsage
>= :: RepositoryCacheUsage -> RepositoryCacheUsage -> Bool
$c>= :: RepositoryCacheUsage -> RepositoryCacheUsage -> Bool
> :: RepositoryCacheUsage -> RepositoryCacheUsage -> Bool
$c> :: RepositoryCacheUsage -> RepositoryCacheUsage -> Bool
<= :: RepositoryCacheUsage -> RepositoryCacheUsage -> Bool
$c<= :: RepositoryCacheUsage -> RepositoryCacheUsage -> Bool
< :: RepositoryCacheUsage -> RepositoryCacheUsage -> Bool
$c< :: RepositoryCacheUsage -> RepositoryCacheUsage -> Bool
compare :: RepositoryCacheUsage -> RepositoryCacheUsage -> Ordering
$ccompare :: RepositoryCacheUsage -> RepositoryCacheUsage -> Ordering
Ord, forall x. Rep RepositoryCacheUsage x -> RepositoryCacheUsage
forall x. RepositoryCacheUsage -> Rep RepositoryCacheUsage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RepositoryCacheUsage x -> RepositoryCacheUsage
$cfrom :: forall x. RepositoryCacheUsage -> Rep RepositoryCacheUsage x
Generic)

data OrganizationCacheUsage = OrganizationCacheUsage
    { OrganizationCacheUsage -> Int
organizationCacheUsageTotalActiveCachesSizeInBytes :: !Int
    , OrganizationCacheUsage -> Int
organizationCacheUsageTotalActiveCachesCount       :: !Int
    }
  deriving (Int -> OrganizationCacheUsage -> ShowS
[OrganizationCacheUsage] -> ShowS
OrganizationCacheUsage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OrganizationCacheUsage] -> ShowS
$cshowList :: [OrganizationCacheUsage] -> ShowS
show :: OrganizationCacheUsage -> String
$cshow :: OrganizationCacheUsage -> String
showsPrec :: Int -> OrganizationCacheUsage -> ShowS
$cshowsPrec :: Int -> OrganizationCacheUsage -> ShowS
Show, Typeable OrganizationCacheUsage
OrganizationCacheUsage -> DataType
OrganizationCacheUsage -> Constr
(forall b. Data b => b -> b)
-> OrganizationCacheUsage -> OrganizationCacheUsage
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> OrganizationCacheUsage -> u
forall u.
(forall d. Data d => d -> u) -> OrganizationCacheUsage -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> OrganizationCacheUsage
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> OrganizationCacheUsage
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OrganizationCacheUsage -> m OrganizationCacheUsage
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrganizationCacheUsage -> m OrganizationCacheUsage
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OrganizationCacheUsage
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OrganizationCacheUsage
-> c OrganizationCacheUsage
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OrganizationCacheUsage)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OrganizationCacheUsage)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrganizationCacheUsage -> m OrganizationCacheUsage
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrganizationCacheUsage -> m OrganizationCacheUsage
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrganizationCacheUsage -> m OrganizationCacheUsage
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrganizationCacheUsage -> m OrganizationCacheUsage
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OrganizationCacheUsage -> m OrganizationCacheUsage
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OrganizationCacheUsage -> m OrganizationCacheUsage
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OrganizationCacheUsage -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OrganizationCacheUsage -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> OrganizationCacheUsage -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> OrganizationCacheUsage -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> OrganizationCacheUsage
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> OrganizationCacheUsage
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> OrganizationCacheUsage
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> OrganizationCacheUsage
-> r
gmapT :: (forall b. Data b => b -> b)
-> OrganizationCacheUsage -> OrganizationCacheUsage
$cgmapT :: (forall b. Data b => b -> b)
-> OrganizationCacheUsage -> OrganizationCacheUsage
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OrganizationCacheUsage)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OrganizationCacheUsage)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OrganizationCacheUsage)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OrganizationCacheUsage)
dataTypeOf :: OrganizationCacheUsage -> DataType
$cdataTypeOf :: OrganizationCacheUsage -> DataType
toConstr :: OrganizationCacheUsage -> Constr
$ctoConstr :: OrganizationCacheUsage -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OrganizationCacheUsage
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OrganizationCacheUsage
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OrganizationCacheUsage
-> c OrganizationCacheUsage
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OrganizationCacheUsage
-> c OrganizationCacheUsage
Data, Typeable, OrganizationCacheUsage -> OrganizationCacheUsage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OrganizationCacheUsage -> OrganizationCacheUsage -> Bool
$c/= :: OrganizationCacheUsage -> OrganizationCacheUsage -> Bool
== :: OrganizationCacheUsage -> OrganizationCacheUsage -> Bool
$c== :: OrganizationCacheUsage -> OrganizationCacheUsage -> Bool
Eq, Eq OrganizationCacheUsage
OrganizationCacheUsage -> OrganizationCacheUsage -> Bool
OrganizationCacheUsage -> OrganizationCacheUsage -> Ordering
OrganizationCacheUsage
-> OrganizationCacheUsage -> OrganizationCacheUsage
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: OrganizationCacheUsage
-> OrganizationCacheUsage -> OrganizationCacheUsage
$cmin :: OrganizationCacheUsage
-> OrganizationCacheUsage -> OrganizationCacheUsage
max :: OrganizationCacheUsage
-> OrganizationCacheUsage -> OrganizationCacheUsage
$cmax :: OrganizationCacheUsage
-> OrganizationCacheUsage -> OrganizationCacheUsage
>= :: OrganizationCacheUsage -> OrganizationCacheUsage -> Bool
$c>= :: OrganizationCacheUsage -> OrganizationCacheUsage -> Bool
> :: OrganizationCacheUsage -> OrganizationCacheUsage -> Bool
$c> :: OrganizationCacheUsage -> OrganizationCacheUsage -> Bool
<= :: OrganizationCacheUsage -> OrganizationCacheUsage -> Bool
$c<= :: OrganizationCacheUsage -> OrganizationCacheUsage -> Bool
< :: OrganizationCacheUsage -> OrganizationCacheUsage -> Bool
$c< :: OrganizationCacheUsage -> OrganizationCacheUsage -> Bool
compare :: OrganizationCacheUsage -> OrganizationCacheUsage -> Ordering
$ccompare :: OrganizationCacheUsage -> OrganizationCacheUsage -> Ordering
Ord, forall x. Rep OrganizationCacheUsage x -> OrganizationCacheUsage
forall x. OrganizationCacheUsage -> Rep OrganizationCacheUsage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OrganizationCacheUsage x -> OrganizationCacheUsage
$cfrom :: forall x. OrganizationCacheUsage -> Rep OrganizationCacheUsage x
Generic)

-------------------------------------------------------------------------------
-- JSON instances
-------------------------------------------------------------------------------

instance FromJSON Cache where
    parseJSON :: Value -> Parser Cache
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Cache" forall a b. (a -> b) -> a -> b
$ \Object
o -> Id Cache
-> Text -> Text -> Text -> UTCTime -> UTCTime -> Int -> Cache
Cache
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"ref"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"key"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"version"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"last_accessed_at"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"created_at"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"size_in_bytes"

instance FromJSON (WithTotalCount Cache) where
    parseJSON :: Value -> Parser (WithTotalCount Cache)
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CacheList" forall a b. (a -> b) -> a -> b
$ \Object
o -> forall a. Vector a -> Int -> WithTotalCount a
WithTotalCount
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"actions_caches"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_count"

instance FromJSON OrganizationCacheUsage where
    parseJSON :: Value -> Parser OrganizationCacheUsage
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"OrganizationCacheUsage" forall a b. (a -> b) -> a -> b
$ \Object
o -> Int -> Int -> OrganizationCacheUsage
OrganizationCacheUsage
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_active_caches_size_in_bytes"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_active_caches_count"

instance FromJSON RepositoryCacheUsage where
    parseJSON :: Value -> Parser RepositoryCacheUsage
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RepositoryCacheUsage" forall a b. (a -> b) -> a -> b
$ \Object
o -> Text -> Int -> Int -> RepositoryCacheUsage
RepositoryCacheUsage
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"full_name"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"active_caches_size_in_bytes"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"active_caches_count"

instance FromJSON (WithTotalCount RepositoryCacheUsage) where
    parseJSON :: Value -> Parser (WithTotalCount RepositoryCacheUsage)
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CacheUsageList" forall a b. (a -> b) -> a -> b
$ \Object
o -> forall a. Vector a -> Int -> WithTotalCount a
WithTotalCount
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"repository_cache_usages"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_count"