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 $cshowsPrec :: Int -> Milestone -> ShowS showsPrec :: Int -> Milestone -> ShowS $cshow :: Milestone -> String show :: Milestone -> String $cshowList :: [Milestone] -> ShowS showList :: [Milestone] -> ShowS Show, Typeable Milestone 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 -> Constr Milestone -> DataType (forall b. Data b => b -> b) -> Milestone -> 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) $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Milestone -> c Milestone gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Milestone -> c Milestone $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Milestone gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Milestone $ctoConstr :: Milestone -> Constr toConstr :: Milestone -> Constr $cdataTypeOf :: Milestone -> DataType dataTypeOf :: Milestone -> DataType $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Milestone) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Milestone) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Milestone) dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Milestone) $cgmapT :: (forall b. Data b => b -> b) -> Milestone -> Milestone gmapT :: (forall b. Data b => b -> b) -> Milestone -> Milestone $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Milestone -> r gmapQl :: forall r r'. (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 gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Milestone -> r $cgmapQ :: forall u. (forall d. Data d => d -> u) -> Milestone -> [u] gmapQ :: forall u. (forall d. Data d => d -> u) -> Milestone -> [u] $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Milestone -> u gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Milestone -> u $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Milestone -> m Milestone gmapM :: forall (m :: * -> *). Monad m => (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 gmapMp :: forall (m :: * -> *). MonadPlus m => (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 gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Milestone -> m Milestone Data, Typeable, Milestone -> Milestone -> Bool (Milestone -> Milestone -> Bool) -> (Milestone -> Milestone -> Bool) -> Eq Milestone forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: Milestone -> Milestone -> Bool == :: Milestone -> Milestone -> Bool $c/= :: Milestone -> Milestone -> Bool /= :: 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 $ccompare :: Milestone -> Milestone -> Ordering compare :: Milestone -> Milestone -> Ordering $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 >= :: Milestone -> Milestone -> Bool $cmax :: Milestone -> Milestone -> Milestone max :: Milestone -> Milestone -> Milestone $cmin :: Milestone -> Milestone -> Milestone min :: Milestone -> Milestone -> 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 $cfrom :: forall x. Milestone -> Rep Milestone x from :: forall x. Milestone -> Rep Milestone x $cto :: forall x. Rep Milestone x -> Milestone to :: forall x. Rep Milestone x -> Milestone 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 a b. Parser (a -> b) -> Parser a -> Parser b 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 a b. Parser (a -> b) -> Parser a -> Parser b 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 a b. Parser (a -> b) -> Parser a -> Parser b 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 a b. Parser (a -> b) -> Parser a -> Parser b 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 a b. Parser (a -> b) -> Parser a -> Parser b 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 a b. Parser (a -> b) -> Parser a -> Parser b 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 a b. Parser (a -> b) -> Parser a -> Parser b 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 a b. Parser (a -> b) -> Parser a -> Parser b 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 a b. Parser (a -> b) -> Parser a -> Parser b 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 $cshowsPrec :: Int -> NewMilestone -> ShowS showsPrec :: Int -> NewMilestone -> ShowS $cshow :: NewMilestone -> String show :: NewMilestone -> String $cshowList :: [NewMilestone] -> ShowS showList :: [NewMilestone] -> ShowS Show, Typeable NewMilestone 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 -> Constr NewMilestone -> DataType (forall b. Data b => b -> b) -> NewMilestone -> 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) $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewMilestone -> c NewMilestone gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewMilestone -> c NewMilestone $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NewMilestone gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NewMilestone $ctoConstr :: NewMilestone -> Constr toConstr :: NewMilestone -> Constr $cdataTypeOf :: NewMilestone -> DataType dataTypeOf :: NewMilestone -> DataType $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NewMilestone) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NewMilestone) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewMilestone) dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewMilestone) $cgmapT :: (forall b. Data b => b -> b) -> NewMilestone -> NewMilestone gmapT :: (forall b. Data b => b -> b) -> NewMilestone -> NewMilestone $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NewMilestone -> r gmapQl :: forall r r'. (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 gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NewMilestone -> r $cgmapQ :: forall u. (forall d. Data d => d -> u) -> NewMilestone -> [u] gmapQ :: forall u. (forall d. Data d => d -> u) -> NewMilestone -> [u] $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NewMilestone -> u gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NewMilestone -> u $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> NewMilestone -> m NewMilestone gmapM :: forall (m :: * -> *). Monad m => (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 gmapMp :: forall (m :: * -> *). MonadPlus m => (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 gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> NewMilestone -> m NewMilestone Data, Typeable, NewMilestone -> NewMilestone -> Bool (NewMilestone -> NewMilestone -> Bool) -> (NewMilestone -> NewMilestone -> Bool) -> Eq NewMilestone forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: NewMilestone -> NewMilestone -> Bool == :: NewMilestone -> NewMilestone -> Bool $c/= :: NewMilestone -> NewMilestone -> Bool /= :: 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 $ccompare :: NewMilestone -> NewMilestone -> Ordering compare :: NewMilestone -> NewMilestone -> Ordering $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 >= :: NewMilestone -> NewMilestone -> Bool $cmax :: NewMilestone -> NewMilestone -> NewMilestone max :: NewMilestone -> NewMilestone -> NewMilestone $cmin :: NewMilestone -> NewMilestone -> NewMilestone min :: NewMilestone -> NewMilestone -> 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 $cfrom :: forall x. NewMilestone -> Rep NewMilestone x from :: forall x. NewMilestone -> Rep NewMilestone x $cto :: forall x. Rep NewMilestone x -> NewMilestone to :: forall x. Rep NewMilestone x -> NewMilestone 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 forall v. ToJSON v => Key -> v -> Pair .= Text title , Key "state" Key -> Text -> Pair forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv forall v. ToJSON v => Key -> v -> Pair .= Text state , Key "description" Key -> Maybe Text -> Pair forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv forall v. ToJSON v => Key -> v -> Pair .= Maybe Text desc , Key "due_on" Key -> Maybe UTCTime -> Pair forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv forall v. ToJSON v => Key -> v -> Pair .= 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 $cshowsPrec :: Int -> UpdateMilestone -> ShowS showsPrec :: Int -> UpdateMilestone -> ShowS $cshow :: UpdateMilestone -> String show :: UpdateMilestone -> String $cshowList :: [UpdateMilestone] -> ShowS showList :: [UpdateMilestone] -> ShowS Show, Typeable UpdateMilestone 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 -> Constr UpdateMilestone -> DataType (forall b. Data b => b -> b) -> UpdateMilestone -> 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) $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateMilestone -> c UpdateMilestone gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateMilestone -> c UpdateMilestone $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateMilestone gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateMilestone $ctoConstr :: UpdateMilestone -> Constr toConstr :: UpdateMilestone -> Constr $cdataTypeOf :: UpdateMilestone -> DataType dataTypeOf :: UpdateMilestone -> DataType $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UpdateMilestone) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UpdateMilestone) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateMilestone) dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateMilestone) $cgmapT :: (forall b. Data b => b -> b) -> UpdateMilestone -> UpdateMilestone gmapT :: (forall b. Data b => b -> b) -> UpdateMilestone -> UpdateMilestone $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpdateMilestone -> r gmapQl :: forall r r'. (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 gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpdateMilestone -> r $cgmapQ :: forall u. (forall d. Data d => d -> u) -> UpdateMilestone -> [u] gmapQ :: forall u. (forall d. Data d => d -> u) -> UpdateMilestone -> [u] $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UpdateMilestone -> u gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UpdateMilestone -> u $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> UpdateMilestone -> m UpdateMilestone gmapM :: forall (m :: * -> *). Monad m => (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 gmapMp :: forall (m :: * -> *). MonadPlus m => (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 gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> UpdateMilestone -> m UpdateMilestone Data, Typeable, UpdateMilestone -> UpdateMilestone -> Bool (UpdateMilestone -> UpdateMilestone -> Bool) -> (UpdateMilestone -> UpdateMilestone -> Bool) -> Eq UpdateMilestone forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: UpdateMilestone -> UpdateMilestone -> Bool == :: UpdateMilestone -> UpdateMilestone -> Bool $c/= :: UpdateMilestone -> UpdateMilestone -> Bool /= :: 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 $ccompare :: UpdateMilestone -> UpdateMilestone -> Ordering compare :: UpdateMilestone -> UpdateMilestone -> Ordering $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 >= :: UpdateMilestone -> UpdateMilestone -> Bool $cmax :: UpdateMilestone -> UpdateMilestone -> UpdateMilestone max :: UpdateMilestone -> UpdateMilestone -> UpdateMilestone $cmin :: UpdateMilestone -> UpdateMilestone -> UpdateMilestone min :: UpdateMilestone -> UpdateMilestone -> 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 $cfrom :: forall x. UpdateMilestone -> Rep UpdateMilestone x from :: forall x. UpdateMilestone -> Rep UpdateMilestone x $cto :: forall x. Rep UpdateMilestone x -> UpdateMilestone to :: forall x. Rep UpdateMilestone x -> UpdateMilestone 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 forall v. ToJSON v => Key -> v -> Pair .= Maybe Text title , Key "state" Key -> Maybe Text -> Pair forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv forall v. ToJSON v => Key -> v -> Pair .= Maybe Text state , Key "description" Key -> Maybe Text -> Pair forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv forall v. ToJSON v => Key -> v -> Pair .= Maybe Text desc , Key "due_on" Key -> Maybe UTCTime -> Pair forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv forall v. ToJSON v => Key -> v -> Pair .= Maybe UTCTime due ] where notNull :: (a, Value) -> Bool notNull (a _, Value Null) = Bool False notNull (a _, Value _) = Bool True