-----------------------------------------------------------------------------
-- |
-- License     :  BSD-3-Clause
-- Maintainer  :  Oleg Grenrus <oleg.grenrus@iki.fi>
--
module GitHub.Data.Milestone where

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

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

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

instance FromJSON Milestone where
    parseJSON :: Value -> Parser Milestone
parseJSON = String -> (Object -> Parser Milestone) -> Value -> Parser Milestone
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Milestone" ((Object -> Parser Milestone) -> Value -> Parser Milestone)
-> (Object -> Parser Milestone) -> Value -> Parser Milestone
forall a b. (a -> b) -> a -> b
$ \Object
o -> SimpleUser
-> Maybe UTCTime
-> Int
-> Id Milestone
-> Int
-> Maybe Text
-> Text
-> URL
-> UTCTime
-> Text
-> Milestone
Milestone
        (SimpleUser
 -> Maybe UTCTime
 -> Int
 -> Id Milestone
 -> Int
 -> Maybe Text
 -> Text
 -> URL
 -> UTCTime
 -> Text
 -> Milestone)
-> Parser SimpleUser
-> Parser
     (Maybe UTCTime
      -> Int
      -> Id Milestone
      -> Int
      -> Maybe Text
      -> Text
      -> URL
      -> UTCTime
      -> Text
      -> Milestone)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser SimpleUser
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"creator"
        Parser
  (Maybe UTCTime
   -> Int
   -> Id Milestone
   -> Int
   -> Maybe Text
   -> Text
   -> URL
   -> UTCTime
   -> Text
   -> Milestone)
-> Parser (Maybe UTCTime)
-> Parser
     (Int
      -> Id Milestone
      -> Int
      -> Maybe Text
      -> Text
      -> URL
      -> UTCTime
      -> Text
      -> Milestone)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe UTCTime)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"due_on"
        Parser
  (Int
   -> Id Milestone
   -> Int
   -> Maybe Text
   -> Text
   -> URL
   -> UTCTime
   -> Text
   -> Milestone)
-> Parser Int
-> Parser
     (Id Milestone
      -> Int
      -> Maybe Text
      -> Text
      -> URL
      -> UTCTime
      -> Text
      -> Milestone)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"open_issues"
        Parser
  (Id Milestone
   -> Int
   -> Maybe Text
   -> Text
   -> URL
   -> UTCTime
   -> Text
   -> Milestone)
-> Parser (Id Milestone)
-> Parser
     (Int -> Maybe Text -> Text -> URL -> UTCTime -> Text -> Milestone)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Id Milestone)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"number"
        Parser
  (Int -> Maybe Text -> Text -> URL -> UTCTime -> Text -> Milestone)
-> Parser Int
-> Parser
     (Maybe Text -> Text -> URL -> UTCTime -> Text -> Milestone)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"closed_issues"
        Parser (Maybe Text -> Text -> URL -> UTCTime -> Text -> Milestone)
-> Parser (Maybe Text)
-> Parser (Text -> URL -> UTCTime -> Text -> Milestone)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"description"
        Parser (Text -> URL -> UTCTime -> Text -> Milestone)
-> Parser Text -> Parser (URL -> UTCTime -> Text -> Milestone)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"title"
        Parser (URL -> UTCTime -> Text -> Milestone)
-> Parser URL -> Parser (UTCTime -> Text -> Milestone)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser URL
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
        Parser (UTCTime -> Text -> Milestone)
-> Parser UTCTime -> Parser (Text -> Milestone)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser UTCTime
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"created_at"
        Parser (Text -> Milestone) -> Parser Text -> Parser Milestone
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"state"

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

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


instance ToJSON NewMilestone where
    toJSON :: NewMilestone -> Value
toJSON (NewMilestone Text
title Text
state Maybe Text
desc Maybe UTCTime
due) = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ (Pair -> Bool) -> [Pair] -> [Pair]
forall a. (a -> Bool) -> [a] -> [a]
filter Pair -> Bool
forall a. (a, Value) -> Bool
notNull
        [ Key
"title"       Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
title
        , Key
"state"       Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
state
        , Key
"description" Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
desc
        , Key
"due_on"      Key -> Maybe UTCTime -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe UTCTime
due
        ]
      where
        notNull :: (a, Value) -> Bool
notNull (a
_, Value
Null) = Bool
False
        notNull (a
_, Value
_)    = Bool
True

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

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


instance ToJSON UpdateMilestone where
  toJSON :: UpdateMilestone -> Value
toJSON (UpdateMilestone Maybe Text
title Maybe Text
state Maybe Text
desc Maybe UTCTime
due) = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ (Pair -> Bool) -> [Pair] -> [Pair]
forall a. (a -> Bool) -> [a] -> [a]
filter Pair -> Bool
forall a. (a, Value) -> Bool
notNull
      [ Key
"title"       Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
title
      , Key
"state"       Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
state
      , Key
"description" Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
desc
      , Key
"due_on"      Key -> Maybe UTCTime -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe UTCTime
due
      ]
    where
      notNull :: (a, Value) -> Bool
notNull (a
_, Value
Null) = Bool
False
      notNull (a
_, Value
_)    = Bool
True