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 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 Milestone -> DataType Milestone -> Constr (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) gmapMo :: 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 gmapMp :: forall (m :: * -> *). MonadPlus 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 gmapM :: forall (m :: * -> *). Monad m => (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 :: forall u. Int -> (forall d. Data d => d -> u) -> Milestone -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Milestone -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> Milestone -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> Milestone -> [u] gmapQr :: 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 gmapQl :: forall r r'. (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 (t :: * -> * -> *) (c :: * -> *). Typeable t => (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 (t :: * -> *) (c :: * -> *). Typeable t => (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 (c :: * -> *). (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 (c :: * -> *). (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 Data, Typeable, Milestone -> Milestone -> Bool 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 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 Ord, 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 = forall a. (Generic a, GNFData (Rep a)) => a -> () genericRnf instance Binary Milestone instance FromJSON Milestone where parseJSON :: Value -> Parser Milestone parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a withObject String "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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o forall a. FromJSON a => Object -> Key -> Parser a .: Key "creator" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o forall a. FromJSON a => Object -> Key -> Parser a .: Key "due_on" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o forall a. FromJSON a => Object -> Key -> Parser a .: Key "open_issues" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o forall a. FromJSON a => Object -> Key -> Parser a .: Key "number" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o forall a. FromJSON a => Object -> Key -> Parser a .: Key "closed_issues" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o forall a. FromJSON a => Object -> Key -> Parser a .: Key "description" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o forall a. FromJSON a => Object -> Key -> Parser a .: Key "title" 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" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o forall a. FromJSON a => Object -> Key -> Parser a .: Key "created_at" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o forall a. FromJSON a => Object -> Key -> Parser a .: Key "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 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 NewMilestone -> DataType NewMilestone -> Constr (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) gmapMo :: 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 gmapMp :: forall (m :: * -> *). MonadPlus 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 gmapM :: forall (m :: * -> *). Monad m => (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 :: forall u. Int -> (forall d. Data d => d -> u) -> NewMilestone -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NewMilestone -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> NewMilestone -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> NewMilestone -> [u] gmapQr :: 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 gmapQl :: forall r r'. (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 (t :: * -> * -> *) (c :: * -> *). Typeable t => (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 (t :: * -> *) (c :: * -> *). Typeable t => (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 (c :: * -> *). (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 (c :: * -> *). (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 Data, Typeable, NewMilestone -> NewMilestone -> Bool 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 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 Ord, 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 = 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 forall a b. (a -> b) -> a -> b $ forall a. (a -> Bool) -> [a] -> [a] filter forall {a}. (a, Value) -> Bool notNull [ Key "title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Text title , Key "state" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Text state , Key "description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Maybe Text desc , Key "due_on" 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 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 UpdateMilestone -> DataType UpdateMilestone -> Constr (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) gmapMo :: 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 gmapMp :: forall (m :: * -> *). MonadPlus 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 gmapM :: forall (m :: * -> *). Monad m => (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 :: forall u. Int -> (forall d. Data d => d -> u) -> UpdateMilestone -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UpdateMilestone -> u gmapQ :: forall u. (forall d. Data d => d -> u) -> UpdateMilestone -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> UpdateMilestone -> [u] gmapQr :: 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 gmapQl :: forall r r'. (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 (t :: * -> * -> *) (c :: * -> *). Typeable t => (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 (t :: * -> *) (c :: * -> *). Typeable t => (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 (c :: * -> *). (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 (c :: * -> *). (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 Data, Typeable, UpdateMilestone -> UpdateMilestone -> Bool 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 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 Ord, 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 = 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 forall a b. (a -> b) -> a -> b $ forall a. (a -> Bool) -> [a] -> [a] filter forall {a}. (a, Value) -> Bool notNull [ Key "title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Maybe Text title , Key "state" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Maybe Text state , Key "description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Maybe Text desc , Key "due_on" 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