-----------------------------------------------------------------------------
-- |
-- License     :  BSD-3-Clause
-- Maintainer  :  Oleg Grenrus <oleg.grenrus@iki.fi>
--
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
(Int -> Gist -> ShowS)
-> (Gist -> String) -> ([Gist] -> ShowS) -> Show Gist
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
DataType
Constr
Typeable Gist
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Gist -> c Gist)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Gist)
-> (Gist -> Constr)
-> (Gist -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> Gist -> Gist)
-> (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 u. (forall d. Data d => d -> u) -> Gist -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Gist -> u)
-> (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 (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Gist -> m Gist)
-> Data Gist
Gist -> DataType
Gist -> Constr
(forall b. Data b => b -> b) -> Gist -> Gist
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Gist -> c Gist
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cGist :: Constr
$tGist :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> Gist -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Gist -> u
gmapQ :: (forall d. Data d => d -> u) -> Gist -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Gist -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable Gist
Data, Typeable, Gist -> Gist -> Bool
(Gist -> Gist -> Bool) -> (Gist -> Gist -> Bool) -> Eq Gist
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. Gist -> Rep Gist x)
-> (forall x. Rep Gist x -> Gist) -> Generic Gist
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 = Gist -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary Gist

instance FromJSON Gist where
    parseJSON :: Value -> Parser Gist
parseJSON = String -> (Object -> Parser Gist) -> Value -> Parser Gist
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Gist" ((Object -> Parser Gist) -> Value -> Parser Gist)
-> (Object -> Parser Gist) -> Value -> Parser 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
        (SimpleUser
 -> URL
 -> URL
 -> Maybe Text
 -> UTCTime
 -> Bool
 -> Int
 -> UTCTime
 -> URL
 -> Name Gist
 -> HashMap Text GistFile
 -> URL
 -> Gist)
-> Parser SimpleUser
-> Parser
     (URL
      -> URL
      -> Maybe Text
      -> UTCTime
      -> Bool
      -> Int
      -> UTCTime
      -> URL
      -> Name Gist
      -> HashMap Text GistFile
      -> URL
      -> Gist)
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
"owner"
        Parser
  (URL
   -> URL
   -> Maybe Text
   -> UTCTime
   -> Bool
   -> Int
   -> UTCTime
   -> URL
   -> Name Gist
   -> HashMap Text GistFile
   -> URL
   -> Gist)
-> Parser URL
-> Parser
     (URL
      -> Maybe Text
      -> UTCTime
      -> Bool
      -> Int
      -> UTCTime
      -> URL
      -> Name Gist
      -> HashMap Text GistFile
      -> URL
      -> Gist)
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
"git_push_url"
        Parser
  (URL
   -> Maybe Text
   -> UTCTime
   -> Bool
   -> Int
   -> UTCTime
   -> URL
   -> Name Gist
   -> HashMap Text GistFile
   -> URL
   -> Gist)
-> Parser URL
-> Parser
     (Maybe Text
      -> UTCTime
      -> Bool
      -> Int
      -> UTCTime
      -> URL
      -> Name Gist
      -> HashMap Text GistFile
      -> URL
      -> Gist)
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
  (Maybe Text
   -> UTCTime
   -> Bool
   -> Int
   -> UTCTime
   -> URL
   -> Name Gist
   -> HashMap Text GistFile
   -> URL
   -> Gist)
-> Parser (Maybe Text)
-> Parser
     (UTCTime
      -> Bool
      -> Int
      -> UTCTime
      -> URL
      -> Name Gist
      -> HashMap Text GistFile
      -> URL
      -> Gist)
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 (Maybe a)
.:? Key
"description"
        Parser
  (UTCTime
   -> Bool
   -> Int
   -> UTCTime
   -> URL
   -> Name Gist
   -> HashMap Text GistFile
   -> URL
   -> Gist)
-> Parser UTCTime
-> Parser
     (Bool
      -> Int
      -> UTCTime
      -> URL
      -> Name Gist
      -> HashMap Text GistFile
      -> URL
      -> Gist)
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
  (Bool
   -> Int
   -> UTCTime
   -> URL
   -> Name Gist
   -> HashMap Text GistFile
   -> URL
   -> Gist)
-> Parser Bool
-> Parser
     (Int
      -> UTCTime
      -> URL
      -> Name Gist
      -> HashMap Text GistFile
      -> URL
      -> Gist)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"public"
        Parser
  (Int
   -> UTCTime
   -> URL
   -> Name Gist
   -> HashMap Text GistFile
   -> URL
   -> Gist)
-> Parser Int
-> Parser
     (UTCTime
      -> URL -> Name Gist -> HashMap Text GistFile -> URL -> Gist)
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
"comments"
        Parser
  (UTCTime
   -> URL -> Name Gist -> HashMap Text GistFile -> URL -> Gist)
-> Parser UTCTime
-> Parser
     (URL -> Name Gist -> HashMap Text GistFile -> URL -> Gist)
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
"updated_at"
        Parser (URL -> Name Gist -> HashMap Text GistFile -> URL -> Gist)
-> Parser URL
-> Parser (Name Gist -> HashMap Text GistFile -> URL -> Gist)
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
"html_url"
        Parser (Name Gist -> HashMap Text GistFile -> URL -> Gist)
-> Parser (Name Gist)
-> Parser (HashMap Text GistFile -> URL -> Gist)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Name Gist)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
        Parser (HashMap Text GistFile -> URL -> Gist)
-> Parser (HashMap Text GistFile) -> Parser (URL -> Gist)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (HashMap Text GistFile)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"files"
        Parser (URL -> Gist) -> Parser URL -> Parser Gist
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
"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
(Int -> GistFile -> ShowS)
-> (GistFile -> String) -> ([GistFile] -> ShowS) -> Show GistFile
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
DataType
Constr
Typeable GistFile
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> GistFile -> c GistFile)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c GistFile)
-> (GistFile -> Constr)
-> (GistFile -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> GistFile -> GistFile)
-> (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 u. (forall d. Data d => d -> u) -> GistFile -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> GistFile -> u)
-> (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 (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> GistFile -> m GistFile)
-> Data GistFile
GistFile -> DataType
GistFile -> Constr
(forall b. Data b => b -> b) -> GistFile -> GistFile
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GistFile -> c GistFile
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cGistFile :: Constr
$tGistFile :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> GistFile -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> GistFile -> u
gmapQ :: (forall d. Data d => d -> u) -> GistFile -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> GistFile -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable GistFile
Data, Typeable, GistFile -> GistFile -> Bool
(GistFile -> GistFile -> Bool)
-> (GistFile -> GistFile -> Bool) -> Eq GistFile
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. GistFile -> Rep GistFile x)
-> (forall x. Rep GistFile x -> GistFile) -> Generic GistFile
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 = GistFile -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary GistFile

instance FromJSON GistFile where
    parseJSON :: Value -> Parser GistFile
parseJSON = String -> (Object -> Parser GistFile) -> Value -> Parser GistFile
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"GistFile" ((Object -> Parser GistFile) -> Value -> Parser GistFile)
-> (Object -> Parser GistFile) -> Value -> Parser GistFile
forall a b. (a -> b) -> a -> b
$ \Object
o -> Text
-> URL -> Int -> Maybe Language -> Text -> Maybe Text -> GistFile
GistFile
        (Text
 -> URL -> Int -> Maybe Language -> Text -> Maybe Text -> GistFile)
-> Parser Text
-> Parser
     (URL -> Int -> Maybe Language -> Text -> Maybe Text -> GistFile)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
        Parser
  (URL -> Int -> Maybe Language -> Text -> Maybe Text -> GistFile)
-> Parser URL
-> Parser (Int -> Maybe Language -> Text -> Maybe Text -> GistFile)
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
"raw_url"
        Parser (Int -> Maybe Language -> Text -> Maybe Text -> GistFile)
-> Parser Int
-> Parser (Maybe Language -> Text -> Maybe Text -> GistFile)
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
"size"
        Parser (Maybe Language -> Text -> Maybe Text -> GistFile)
-> Parser (Maybe Language)
-> Parser (Text -> Maybe Text -> GistFile)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Language)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"language"
        Parser (Text -> Maybe Text -> GistFile)
-> Parser Text -> Parser (Maybe Text -> GistFile)
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
"filename"
        Parser (Maybe Text -> GistFile)
-> Parser (Maybe Text) -> Parser GistFile
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 (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
(Int -> GistComment -> ShowS)
-> (GistComment -> String)
-> ([GistComment] -> ShowS)
-> Show GistComment
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
DataType
Constr
Typeable GistComment
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> GistComment -> c GistComment)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c GistComment)
-> (GistComment -> Constr)
-> (GistComment -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> GistComment -> GistComment)
-> (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 u. (forall d. Data d => d -> u) -> GistComment -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> GistComment -> u)
-> (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 (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> GistComment -> m GistComment)
-> Data GistComment
GistComment -> DataType
GistComment -> Constr
(forall b. Data b => b -> b) -> GistComment -> GistComment
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GistComment -> c GistComment
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cGistComment :: Constr
$tGistComment :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> GistComment -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> GistComment -> u
gmapQ :: (forall d. Data d => d -> u) -> GistComment -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> GistComment -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable GistComment
Data, Typeable, GistComment -> GistComment -> Bool
(GistComment -> GistComment -> Bool)
-> (GistComment -> GistComment -> Bool) -> Eq GistComment
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
Eq GistComment
-> (GistComment -> GistComment -> Ordering)
-> (GistComment -> GistComment -> Bool)
-> (GistComment -> GistComment -> Bool)
-> (GistComment -> GistComment -> Bool)
-> (GistComment -> GistComment -> Bool)
-> (GistComment -> GistComment -> GistComment)
-> (GistComment -> GistComment -> GistComment)
-> Ord 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
$cp1Ord :: Eq GistComment
Ord, (forall x. GistComment -> Rep GistComment x)
-> (forall x. Rep GistComment x -> GistComment)
-> Generic GistComment
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 = GistComment -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary GistComment

instance FromJSON GistComment where
    parseJSON :: Value -> Parser GistComment
parseJSON = String
-> (Object -> Parser GistComment) -> Value -> Parser GistComment
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"GistComment" ((Object -> Parser GistComment) -> Value -> Parser GistComment)
-> (Object -> Parser GistComment) -> Value -> Parser GistComment
forall a b. (a -> b) -> a -> b
$ \Object
o -> SimpleUser
-> URL
-> UTCTime
-> Text
-> UTCTime
-> Id GistComment
-> GistComment
GistComment
        (SimpleUser
 -> URL
 -> UTCTime
 -> Text
 -> UTCTime
 -> Id GistComment
 -> GistComment)
-> Parser SimpleUser
-> Parser
     (URL
      -> UTCTime -> Text -> UTCTime -> Id GistComment -> GistComment)
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
"user"
        Parser
  (URL
   -> UTCTime -> Text -> UTCTime -> Id GistComment -> GistComment)
-> Parser URL
-> Parser
     (UTCTime -> Text -> UTCTime -> Id GistComment -> GistComment)
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 -> UTCTime -> Id GistComment -> GistComment)
-> Parser UTCTime
-> Parser (Text -> UTCTime -> Id GistComment -> GistComment)
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 -> UTCTime -> Id GistComment -> GistComment)
-> Parser Text -> Parser (UTCTime -> Id GistComment -> GistComment)
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
"body"
        Parser (UTCTime -> Id GistComment -> GistComment)
-> Parser UTCTime -> Parser (Id GistComment -> GistComment)
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
"updated_at"
        Parser (Id GistComment -> GistComment)
-> Parser (Id GistComment) -> Parser GistComment
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Id GistComment)
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
(Int -> NewGist -> ShowS)
-> (NewGist -> String) -> ([NewGist] -> ShowS) -> Show NewGist
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
DataType
Constr
Typeable NewGist
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> NewGist -> c NewGist)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c NewGist)
-> (NewGist -> Constr)
-> (NewGist -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> NewGist -> NewGist)
-> (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 u. (forall d. Data d => d -> u) -> NewGist -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> NewGist -> u)
-> (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 (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> NewGist -> m NewGist)
-> Data NewGist
NewGist -> DataType
NewGist -> Constr
(forall b. Data b => b -> b) -> NewGist -> NewGist
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewGist -> c NewGist
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cNewGist :: Constr
$tNewGist :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> NewGist -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NewGist -> u
gmapQ :: (forall d. Data d => d -> u) -> NewGist -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NewGist -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable NewGist
Data, Typeable, NewGist -> NewGist -> Bool
(NewGist -> NewGist -> Bool)
-> (NewGist -> NewGist -> Bool) -> Eq NewGist
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. NewGist -> Rep NewGist x)
-> (forall x. Rep NewGist x -> NewGist) -> Generic NewGist
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 = NewGist -> ()
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 ([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
"description"      Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
description
                   , Key
"files"            Key -> HashMap Text NewGistFile -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= HashMap Text NewGistFile
files
                   , Key
"public"           Key -> Maybe Bool -> Pair
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
(Int -> NewGistFile -> ShowS)
-> (NewGistFile -> String)
-> ([NewGistFile] -> ShowS)
-> Show NewGistFile
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
DataType
Constr
Typeable NewGistFile
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> NewGistFile -> c NewGistFile)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c NewGistFile)
-> (NewGistFile -> Constr)
-> (NewGistFile -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> NewGistFile -> NewGistFile)
-> (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 u. (forall d. Data d => d -> u) -> NewGistFile -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> NewGistFile -> u)
-> (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 (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> NewGistFile -> m NewGistFile)
-> Data NewGistFile
NewGistFile -> DataType
NewGistFile -> Constr
(forall b. Data b => b -> b) -> NewGistFile -> NewGistFile
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewGistFile -> c NewGistFile
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cNewGistFile :: Constr
$tNewGistFile :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> NewGistFile -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NewGistFile -> u
gmapQ :: (forall d. Data d => d -> u) -> NewGistFile -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NewGistFile -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable NewGistFile
Data, Typeable, NewGistFile -> NewGistFile -> Bool
(NewGistFile -> NewGistFile -> Bool)
-> (NewGistFile -> NewGistFile -> Bool) -> Eq NewGistFile
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. NewGistFile -> Rep NewGistFile x)
-> (forall x. Rep NewGistFile x -> NewGistFile)
-> Generic NewGistFile
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 = NewGistFile -> ()
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" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
c]