{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
module GitHub.Types.Base.User where
import Data.Aeson (FromJSON (..), ToJSON (..), object)
import Data.Aeson.Types (Value (..), (.:), (.:?), (.=))
import Data.Text (Text)
import Data.Text.Arbitrary ()
import Test.QuickCheck.Arbitrary (Arbitrary (..))
data User = User
{ User -> Text
userAvatarUrl :: Text
, User -> Maybe Text
userEmail :: Maybe Text
, User -> Text
userEventsUrl :: Text
, User -> Text
userFollowersUrl :: Text
, User -> Text
userFollowingUrl :: Text
, User -> Text
userGistsUrl :: Text
, User -> Text
userGravatarId :: Text
, User -> Text
userHtmlUrl :: Text
, User -> Int
userId :: Int
, User -> Text
userLogin :: Text
, User -> Maybe Text
userName :: Maybe Text
, User -> Text
userNodeId :: Text
, User -> Text
userOrganizationsUrl :: Text
, User -> Text
userReceivedEventsUrl :: Text
, User -> Text
userReposUrl :: Text
, User -> Bool
userSiteAdmin :: Bool
, User -> Text
userStarredUrl :: Text
, User -> Text
userSubscriptionsUrl :: Text
, User -> Text
userType :: Text
, User -> Text
userUrl :: Text
} deriving (User -> User -> Bool
(User -> User -> Bool) -> (User -> User -> Bool) -> Eq User
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: User -> User -> Bool
$c/= :: User -> User -> Bool
== :: User -> User -> Bool
$c== :: User -> User -> Bool
Eq, Int -> User -> ShowS
[User] -> ShowS
User -> String
(Int -> User -> ShowS)
-> (User -> String) -> ([User] -> ShowS) -> Show User
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [User] -> ShowS
$cshowList :: [User] -> ShowS
show :: User -> String
$cshow :: User -> String
showsPrec :: Int -> User -> ShowS
$cshowsPrec :: Int -> User -> ShowS
Show, ReadPrec [User]
ReadPrec User
Int -> ReadS User
ReadS [User]
(Int -> ReadS User)
-> ReadS [User] -> ReadPrec User -> ReadPrec [User] -> Read User
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [User]
$creadListPrec :: ReadPrec [User]
readPrec :: ReadPrec User
$creadPrec :: ReadPrec User
readList :: ReadS [User]
$creadList :: ReadS [User]
readsPrec :: Int -> ReadS User
$creadsPrec :: Int -> ReadS User
Read)
instance FromJSON User where
parseJSON :: Value -> Parser User
parseJSON (Object Object
x) = Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User
User
(Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Parser Text
-> Parser
(Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"avatar_url"
Parser
(Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Parser (Maybe Text)
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"email"
Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"events_url"
Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"followers_url"
Parser
(Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"following_url"
Parser
(Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Parser Text
-> Parser
(Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"gists_url"
Parser
(Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Parser Text
-> Parser
(Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"gravatar_id"
Parser
(Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Parser Text
-> Parser
(Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"html_url"
Parser
(Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Parser Int
-> Parser
(Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
Parser
(Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Parser Text
-> Parser
(Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"login"
Parser
(Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Parser (Maybe Text)
-> Parser
(Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"name"
Parser
(Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Parser Text
-> Parser
(Text
-> Text -> Text -> Bool -> Text -> Text -> Text -> Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"node_id"
Parser
(Text
-> Text -> Text -> Bool -> Text -> Text -> Text -> Text -> User)
-> Parser Text
-> Parser
(Text -> Text -> Bool -> Text -> Text -> Text -> Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"organizations_url"
Parser
(Text -> Text -> Bool -> Text -> Text -> Text -> Text -> User)
-> Parser Text
-> Parser (Text -> Bool -> Text -> Text -> Text -> Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"received_events_url"
Parser (Text -> Bool -> Text -> Text -> Text -> Text -> User)
-> Parser Text
-> Parser (Bool -> Text -> Text -> Text -> Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"repos_url"
Parser (Bool -> Text -> Text -> Text -> Text -> User)
-> Parser Bool -> Parser (Text -> Text -> Text -> Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"site_admin"
Parser (Text -> Text -> Text -> Text -> User)
-> Parser Text -> Parser (Text -> Text -> Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"starred_url"
Parser (Text -> Text -> Text -> User)
-> Parser Text -> Parser (Text -> Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"subscriptions_url"
Parser (Text -> Text -> User)
-> Parser Text -> Parser (Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Parser (Text -> User) -> Parser Text -> Parser User
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
parseJSON Value
_ = String -> Parser User
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"User"
instance ToJSON User where
toJSON :: User -> Value
toJSON User{Bool
Int
Maybe Text
Text
userUrl :: Text
userType :: Text
userSubscriptionsUrl :: Text
userStarredUrl :: Text
userSiteAdmin :: Bool
userReposUrl :: Text
userReceivedEventsUrl :: Text
userOrganizationsUrl :: Text
userNodeId :: Text
userName :: Maybe Text
userLogin :: Text
userId :: Int
userHtmlUrl :: Text
userGravatarId :: Text
userGistsUrl :: Text
userFollowingUrl :: Text
userFollowersUrl :: Text
userEventsUrl :: Text
userEmail :: Maybe Text
userAvatarUrl :: Text
userUrl :: User -> Text
userType :: User -> Text
userSubscriptionsUrl :: User -> Text
userStarredUrl :: User -> Text
userSiteAdmin :: User -> Bool
userReposUrl :: User -> Text
userReceivedEventsUrl :: User -> Text
userOrganizationsUrl :: User -> Text
userNodeId :: User -> Text
userName :: User -> Maybe Text
userLogin :: User -> Text
userId :: User -> Int
userHtmlUrl :: User -> Text
userGravatarId :: User -> Text
userGistsUrl :: User -> Text
userFollowingUrl :: User -> Text
userFollowersUrl :: User -> Text
userEventsUrl :: User -> Text
userEmail :: User -> Maybe Text
userAvatarUrl :: User -> Text
..} = [Pair] -> Value
object
[ Key
"avatar_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
userAvatarUrl
, Key
"email" Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
userEmail
, Key
"events_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
userEventsUrl
, Key
"followers_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
userFollowersUrl
, Key
"following_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
userFollowingUrl
, Key
"gists_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
userGistsUrl
, Key
"gravatar_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
userGravatarId
, Key
"html_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
userHtmlUrl
, Key
"id" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
userId
, Key
"login" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
userLogin
, Key
"name" Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
userName
, Key
"node_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
userNodeId
, Key
"organizations_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
userOrganizationsUrl
, Key
"received_events_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
userReceivedEventsUrl
, Key
"repos_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
userReposUrl
, Key
"site_admin" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
userSiteAdmin
, Key
"starred_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
userStarredUrl
, Key
"subscriptions_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
userSubscriptionsUrl
, Key
"type" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
userType
, Key
"url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
userUrl
]
instance Arbitrary User where
arbitrary :: Gen User
arbitrary = Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User
User
(Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Gen Text
-> Gen
(Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Gen (Maybe Text)
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Text)
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Gen Text
-> Gen
(Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Gen Text
-> Gen
(Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Gen Text
-> Gen
(Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Int
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Gen Int
-> Gen
(Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Gen Text
-> Gen
(Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Gen (Maybe Text)
-> Gen
(Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Text)
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> User)
-> Gen Text
-> Gen
(Text
-> Text -> Text -> Bool -> Text -> Text -> Text -> Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Text -> Text -> Bool -> Text -> Text -> Text -> Text -> User)
-> Gen Text
-> Gen
(Text -> Text -> Bool -> Text -> Text -> Text -> Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Text -> Bool -> Text -> Text -> Text -> Text -> User)
-> Gen Text
-> Gen (Text -> Bool -> Text -> Text -> Text -> Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Bool -> Text -> Text -> Text -> Text -> User)
-> Gen Text -> Gen (Bool -> Text -> Text -> Text -> Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Bool -> Text -> Text -> Text -> Text -> User)
-> Gen Bool -> Gen (Text -> Text -> Text -> Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Bool
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Text -> Text -> Text -> User)
-> Gen Text -> Gen (Text -> Text -> Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Text -> Text -> User)
-> Gen Text -> Gen (Text -> Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Text -> User) -> Gen Text -> Gen (Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> User) -> Gen Text -> Gen User
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary