module GitHub.Data.Gists where

import GitHub.Data.Definitions
import GitHub.Data.Id          (Id)
import GitHub.Data.Name        (Name)
import GitHub.Data.Repos       (Language)
import GitHub.Data.URL         (URL)
import GitHub.Internal.Prelude
import Prelude ()

data Gist = Gist
    { Gist -> SimpleUser
gistUser        :: !SimpleUser
    , Gist -> URL
gistGitPushUrl  :: !URL
    , Gist -> URL
gistUrl         :: !URL
    , Gist -> Maybe Text
gistDescription :: !(Maybe Text)
    , Gist -> UTCTime
gistCreatedAt   :: !UTCTime
    , Gist -> Bool
gistPublic      :: !Bool
    , Gist -> Int
gistComments    :: !Int
    , Gist -> UTCTime
gistUpdatedAt   :: !UTCTime
    , Gist -> URL
gistHtmlUrl     :: !URL
    , Gist -> Name Gist
gistId          :: !(Name Gist)
    , Gist -> HashMap Text GistFile
gistFiles       :: !(HashMap Text GistFile)
    , Gist -> URL
gistGitPullUrl  :: !URL
    } deriving (Int -> Gist -> ShowS
[Gist] -> ShowS
Gist -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Gist] -> ShowS
$cshowList :: [Gist] -> ShowS
show :: Gist -> String
$cshow :: Gist -> String
showsPrec :: Int -> Gist -> ShowS
$cshowsPrec :: Int -> Gist -> ShowS
Show, Typeable Gist
Gist -> DataType
Gist -> Constr
(forall b. Data b => b -> b) -> Gist -> Gist
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) -> Gist -> u
forall u. (forall d. Data d => d -> u) -> Gist -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Gist -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Gist -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Gist -> m Gist
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Gist -> m Gist
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Gist
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Gist -> c Gist
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Gist)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Gist)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Gist -> m Gist
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Gist -> m Gist
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Gist -> m Gist
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Gist -> m Gist
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Gist -> m Gist
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Gist -> m Gist
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Gist -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Gist -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Gist -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Gist -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Gist -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Gist -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Gist -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Gist -> r
gmapT :: (forall b. Data b => b -> b) -> Gist -> Gist
$cgmapT :: (forall b. Data b => b -> b) -> Gist -> Gist
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Gist)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Gist)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Gist)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Gist)
dataTypeOf :: Gist -> DataType
$cdataTypeOf :: Gist -> DataType
toConstr :: Gist -> Constr
$ctoConstr :: Gist -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Gist
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Gist
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Gist -> c Gist
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Gist -> c Gist
Data, Typeable, Gist -> Gist -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Gist -> Gist -> Bool
$c/= :: Gist -> Gist -> Bool
== :: Gist -> Gist -> Bool
$c== :: Gist -> Gist -> Bool
Eq, forall x. Rep Gist x -> Gist
forall x. Gist -> Rep Gist x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Gist x -> Gist
$cfrom :: forall x. Gist -> Rep Gist x
Generic)

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

instance FromJSON Gist where
    parseJSON :: Value -> Parser Gist
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Gist" forall a b. (a -> b) -> a -> b
$ \Object
o -> SimpleUser
-> URL
-> URL
-> Maybe Text
-> UTCTime
-> Bool
-> Int
-> UTCTime
-> URL
-> Name Gist
-> HashMap Text GistFile
-> URL
-> Gist
Gist
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"owner"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"git_push_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
"url"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe 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
"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
"public"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"comments"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"updated_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
"html_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
"id"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"files"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"git_push_url"

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

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

instance FromJSON GistFile where
    parseJSON :: Value -> Parser GistFile
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"GistFile" forall a b. (a -> b) -> a -> b
$ \Object
o -> Text
-> URL -> Int -> Maybe Language -> Text -> Maybe Text -> GistFile
GistFile
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"raw_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
"size"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"language"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"filename"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"content"

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

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

instance FromJSON GistComment where
    parseJSON :: Value -> Parser GistComment
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"GistComment" forall a b. (a -> b) -> a -> b
$ \Object
o -> SimpleUser
-> URL
-> UTCTime
-> Text
-> UTCTime
-> Id GistComment
-> GistComment
GistComment
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"user"
        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
"body"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"updated_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
"id"

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

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

instance ToJSON NewGist where
    toJSON :: NewGist -> Value
toJSON NewGist { newGistDescription :: NewGist -> Maybe Text
newGistDescription = Maybe Text
description
                   , newGistFiles :: NewGist -> HashMap Text NewGistFile
newGistFiles       = HashMap Text NewGistFile
files
                   , newGistPublic :: NewGist -> Maybe Bool
newGistPublic      = Maybe Bool
public
                   } = [Pair] -> Value
object forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter forall {a}. (a, Value) -> Bool
notNull
                   [ Key
"description"      forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
description
                   , Key
"files"            forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= HashMap Text NewGistFile
files
                   , Key
"public"           forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
public
                   ]
      where
        notNull :: (a, Value) -> Bool
notNull (a
_, Value
Null) = Bool
False
        notNull (a
_, Value
_)    = Bool
True

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

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

instance ToJSON NewGistFile where
    toJSON :: NewGistFile -> Value
toJSON (NewGistFile Text
c) = [Pair] -> Value
object [Key
"content" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
c]