module GitHub.Data.Enterprise.Organizations where

import GitHub.Data.Definitions
import GitHub.Data.Name (Name)
import GitHub.Data.URL (URL)
import GitHub.Internal.Prelude
import Prelude ()

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

instance NFData CreateOrganization where rnf :: CreateOrganization -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary CreateOrganization

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

instance NFData RenameOrganization where rnf :: RenameOrganization -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary RenameOrganization

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

instance NFData RenameOrganizationResponse where rnf :: RenameOrganizationResponse -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary RenameOrganizationResponse

-- JSON Instances

instance ToJSON CreateOrganization where
    toJSON :: CreateOrganization -> Value
toJSON (CreateOrganization Name Organization
login Name User
admin Maybe Text
profileName) =
        [Pair] -> Value
object forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter forall {a}. (a, Value) -> Bool
notNull
            [ Key
"login"        forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Name Organization
login
            , Key
"admin"        forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Name User
admin
            , Key
"profile_name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
profileName
            ]
      where
        notNull :: (a, Value) -> Bool
notNull (a
_, Value
Null) = Bool
False
        notNull (a
_, Value
_) = Bool
True

instance ToJSON RenameOrganization where
    toJSON :: RenameOrganization -> Value
toJSON (RenameOrganization Name Organization
login) =
        [Pair] -> Value
object
            [ Key
"login" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Name Organization
login
            ]

instance FromJSON RenameOrganizationResponse where
    parseJSON :: Value -> Parser RenameOrganizationResponse
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RenameOrganizationResponse" forall a b. (a -> b) -> a -> b
$ \Object
o ->
        Text -> URL -> RenameOrganizationResponse
RenameOrganizationResponse
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"message"
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"