{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE StandaloneDeriving #-}
module GitHub.Data.Request (
Request,
GenRequest (..),
query, pagedQuery, command,
RW(..),
CommandMethod(..),
toMethod,
FetchCount(..),
MediaType (..),
Paths,
IsPathPart(..),
QueryString,
Count,
) where
import GitHub.Data.Definitions (Count, IssueNumber, QueryString, unIssueNumber)
import GitHub.Data.Id (Id, untagId)
import GitHub.Data.Name (Name, untagName)
import GitHub.Internal.Prelude
import qualified Data.ByteString.Lazy as LBS
import qualified Data.Text as T
import qualified Network.HTTP.Types.Method as Method
type Paths = [Text]
class IsPathPart a where
toPathPart :: a -> Text
instance IsPathPart (Name a) where
toPathPart :: Name a -> Text
toPathPart = forall a. Name a -> Text
untagName
instance IsPathPart (Id a) where
toPathPart :: Id a -> Text
toPathPart = String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall entity. Id entity -> Int
untagId
instance IsPathPart IssueNumber where
toPathPart :: IssueNumber -> Text
toPathPart = String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. IssueNumber -> Int
unIssueNumber
data CommandMethod
= Post
| Patch
| Put
| Delete
deriving (CommandMethod -> CommandMethod -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandMethod -> CommandMethod -> Bool
$c/= :: CommandMethod -> CommandMethod -> Bool
== :: CommandMethod -> CommandMethod -> Bool
$c== :: CommandMethod -> CommandMethod -> Bool
Eq, Eq CommandMethod
CommandMethod -> CommandMethod -> Bool
CommandMethod -> CommandMethod -> Ordering
CommandMethod -> CommandMethod -> CommandMethod
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 :: CommandMethod -> CommandMethod -> CommandMethod
$cmin :: CommandMethod -> CommandMethod -> CommandMethod
max :: CommandMethod -> CommandMethod -> CommandMethod
$cmax :: CommandMethod -> CommandMethod -> CommandMethod
>= :: CommandMethod -> CommandMethod -> Bool
$c>= :: CommandMethod -> CommandMethod -> Bool
> :: CommandMethod -> CommandMethod -> Bool
$c> :: CommandMethod -> CommandMethod -> Bool
<= :: CommandMethod -> CommandMethod -> Bool
$c<= :: CommandMethod -> CommandMethod -> Bool
< :: CommandMethod -> CommandMethod -> Bool
$c< :: CommandMethod -> CommandMethod -> Bool
compare :: CommandMethod -> CommandMethod -> Ordering
$ccompare :: CommandMethod -> CommandMethod -> Ordering
Ord, ReadPrec [CommandMethod]
ReadPrec CommandMethod
Int -> ReadS CommandMethod
ReadS [CommandMethod]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CommandMethod]
$creadListPrec :: ReadPrec [CommandMethod]
readPrec :: ReadPrec CommandMethod
$creadPrec :: ReadPrec CommandMethod
readList :: ReadS [CommandMethod]
$creadList :: ReadS [CommandMethod]
readsPrec :: Int -> ReadS CommandMethod
$creadsPrec :: Int -> ReadS CommandMethod
Read, Int -> CommandMethod -> ShowS
[CommandMethod] -> ShowS
CommandMethod -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandMethod] -> ShowS
$cshowList :: [CommandMethod] -> ShowS
show :: CommandMethod -> String
$cshow :: CommandMethod -> String
showsPrec :: Int -> CommandMethod -> ShowS
$cshowsPrec :: Int -> CommandMethod -> ShowS
Show, Int -> CommandMethod
CommandMethod -> Int
CommandMethod -> [CommandMethod]
CommandMethod -> CommandMethod
CommandMethod -> CommandMethod -> [CommandMethod]
CommandMethod -> CommandMethod -> CommandMethod -> [CommandMethod]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: CommandMethod -> CommandMethod -> CommandMethod -> [CommandMethod]
$cenumFromThenTo :: CommandMethod -> CommandMethod -> CommandMethod -> [CommandMethod]
enumFromTo :: CommandMethod -> CommandMethod -> [CommandMethod]
$cenumFromTo :: CommandMethod -> CommandMethod -> [CommandMethod]
enumFromThen :: CommandMethod -> CommandMethod -> [CommandMethod]
$cenumFromThen :: CommandMethod -> CommandMethod -> [CommandMethod]
enumFrom :: CommandMethod -> [CommandMethod]
$cenumFrom :: CommandMethod -> [CommandMethod]
fromEnum :: CommandMethod -> Int
$cfromEnum :: CommandMethod -> Int
toEnum :: Int -> CommandMethod
$ctoEnum :: Int -> CommandMethod
pred :: CommandMethod -> CommandMethod
$cpred :: CommandMethod -> CommandMethod
succ :: CommandMethod -> CommandMethod
$csucc :: CommandMethod -> CommandMethod
Enum, CommandMethod
forall a. a -> a -> Bounded a
maxBound :: CommandMethod
$cmaxBound :: CommandMethod
minBound :: CommandMethod
$cminBound :: CommandMethod
Bounded, Typeable, Typeable CommandMethod
CommandMethod -> DataType
CommandMethod -> Constr
(forall b. Data b => b -> b) -> CommandMethod -> CommandMethod
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) -> CommandMethod -> u
forall u. (forall d. Data d => d -> u) -> CommandMethod -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CommandMethod -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CommandMethod -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CommandMethod -> m CommandMethod
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CommandMethod -> m CommandMethod
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CommandMethod
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CommandMethod -> c CommandMethod
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CommandMethod)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CommandMethod)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CommandMethod -> m CommandMethod
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CommandMethod -> m CommandMethod
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CommandMethod -> m CommandMethod
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CommandMethod -> m CommandMethod
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CommandMethod -> m CommandMethod
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CommandMethod -> m CommandMethod
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CommandMethod -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CommandMethod -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> CommandMethod -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> CommandMethod -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CommandMethod -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CommandMethod -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CommandMethod -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CommandMethod -> r
gmapT :: (forall b. Data b => b -> b) -> CommandMethod -> CommandMethod
$cgmapT :: (forall b. Data b => b -> b) -> CommandMethod -> CommandMethod
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CommandMethod)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CommandMethod)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CommandMethod)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CommandMethod)
dataTypeOf :: CommandMethod -> DataType
$cdataTypeOf :: CommandMethod -> DataType
toConstr :: CommandMethod -> Constr
$ctoConstr :: CommandMethod -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CommandMethod
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CommandMethod
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CommandMethod -> c CommandMethod
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CommandMethod -> c CommandMethod
Data, forall x. Rep CommandMethod x -> CommandMethod
forall x. CommandMethod -> Rep CommandMethod x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CommandMethod x -> CommandMethod
$cfrom :: forall x. CommandMethod -> Rep CommandMethod x
Generic)
instance Hashable CommandMethod
toMethod :: CommandMethod -> Method.Method
toMethod :: CommandMethod -> Method
toMethod CommandMethod
Post = Method
Method.methodPost
toMethod CommandMethod
Patch = Method
Method.methodPatch
toMethod CommandMethod
Put = Method
Method.methodPut
toMethod CommandMethod
Delete = Method
Method.methodDelete
data FetchCount = FetchAtLeast !Word | FetchAll
deriving (FetchCount -> FetchCount -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FetchCount -> FetchCount -> Bool
$c/= :: FetchCount -> FetchCount -> Bool
== :: FetchCount -> FetchCount -> Bool
$c== :: FetchCount -> FetchCount -> Bool
Eq, Eq FetchCount
FetchCount -> FetchCount -> Bool
FetchCount -> FetchCount -> Ordering
FetchCount -> FetchCount -> FetchCount
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 :: FetchCount -> FetchCount -> FetchCount
$cmin :: FetchCount -> FetchCount -> FetchCount
max :: FetchCount -> FetchCount -> FetchCount
$cmax :: FetchCount -> FetchCount -> FetchCount
>= :: FetchCount -> FetchCount -> Bool
$c>= :: FetchCount -> FetchCount -> Bool
> :: FetchCount -> FetchCount -> Bool
$c> :: FetchCount -> FetchCount -> Bool
<= :: FetchCount -> FetchCount -> Bool
$c<= :: FetchCount -> FetchCount -> Bool
< :: FetchCount -> FetchCount -> Bool
$c< :: FetchCount -> FetchCount -> Bool
compare :: FetchCount -> FetchCount -> Ordering
$ccompare :: FetchCount -> FetchCount -> Ordering
Ord, ReadPrec [FetchCount]
ReadPrec FetchCount
Int -> ReadS FetchCount
ReadS [FetchCount]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FetchCount]
$creadListPrec :: ReadPrec [FetchCount]
readPrec :: ReadPrec FetchCount
$creadPrec :: ReadPrec FetchCount
readList :: ReadS [FetchCount]
$creadList :: ReadS [FetchCount]
readsPrec :: Int -> ReadS FetchCount
$creadsPrec :: Int -> ReadS FetchCount
Read, Int -> FetchCount -> ShowS
[FetchCount] -> ShowS
FetchCount -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FetchCount] -> ShowS
$cshowList :: [FetchCount] -> ShowS
show :: FetchCount -> String
$cshow :: FetchCount -> String
showsPrec :: Int -> FetchCount -> ShowS
$cshowsPrec :: Int -> FetchCount -> ShowS
Show, forall x. Rep FetchCount x -> FetchCount
forall x. FetchCount -> Rep FetchCount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FetchCount x -> FetchCount
$cfrom :: forall x. FetchCount -> Rep FetchCount x
Generic, Typeable)
instance Num FetchCount where
fromInteger :: Integer -> FetchCount
fromInteger = Word -> FetchCount
FetchAtLeast forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger
FetchAtLeast Word
a + :: FetchCount -> FetchCount -> FetchCount
+ FetchAtLeast Word
b = Word -> FetchCount
FetchAtLeast (Word
a forall a. Num a => a -> a -> a
* Word
b)
FetchCount
_ + FetchCount
_ = FetchCount
FetchAll
FetchAtLeast Word
a * :: FetchCount -> FetchCount -> FetchCount
* FetchAtLeast Word
b = Word -> FetchCount
FetchAtLeast (Word
a forall a. Num a => a -> a -> a
* Word
b)
FetchCount
_ * FetchCount
_ = FetchCount
FetchAll
abs :: FetchCount -> FetchCount
abs = forall a. HasCallStack => String -> a
error String
"abs @FetchCount: not implemented"
signum :: FetchCount -> FetchCount
signum = forall a. HasCallStack => String -> a
error String
"signum @FetchCount: not implemented"
negate :: FetchCount -> FetchCount
negate = forall a. HasCallStack => String -> a
error String
"negate @FetchCount: not implemented"
instance Hashable FetchCount
instance Binary FetchCount
instance NFData FetchCount where rnf :: FetchCount -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
data MediaType a
= MtJSON
| MtRaw
| MtDiff
| MtPatch
| MtSha
| MtStar
| MtRedirect
| MtStatus
| MtUnit
| MtPreview a
deriving (MediaType a -> MediaType a -> Bool
forall a. Eq a => MediaType a -> MediaType a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MediaType a -> MediaType a -> Bool
$c/= :: forall a. Eq a => MediaType a -> MediaType a -> Bool
== :: MediaType a -> MediaType a -> Bool
$c== :: forall a. Eq a => MediaType a -> MediaType a -> Bool
Eq, MediaType a -> MediaType a -> Ordering
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
forall {a}. Ord a => Eq (MediaType a)
forall a. Ord a => MediaType a -> MediaType a -> Bool
forall a. Ord a => MediaType a -> MediaType a -> Ordering
forall a. Ord a => MediaType a -> MediaType a -> MediaType a
min :: MediaType a -> MediaType a -> MediaType a
$cmin :: forall a. Ord a => MediaType a -> MediaType a -> MediaType a
max :: MediaType a -> MediaType a -> MediaType a
$cmax :: forall a. Ord a => MediaType a -> MediaType a -> MediaType a
>= :: MediaType a -> MediaType a -> Bool
$c>= :: forall a. Ord a => MediaType a -> MediaType a -> Bool
> :: MediaType a -> MediaType a -> Bool
$c> :: forall a. Ord a => MediaType a -> MediaType a -> Bool
<= :: MediaType a -> MediaType a -> Bool
$c<= :: forall a. Ord a => MediaType a -> MediaType a -> Bool
< :: MediaType a -> MediaType a -> Bool
$c< :: forall a. Ord a => MediaType a -> MediaType a -> Bool
compare :: MediaType a -> MediaType a -> Ordering
$ccompare :: forall a. Ord a => MediaType a -> MediaType a -> Ordering
Ord, ReadPrec [MediaType a]
ReadPrec (MediaType a)
ReadS [MediaType a]
forall a. Read a => ReadPrec [MediaType a]
forall a. Read a => ReadPrec (MediaType a)
forall a. Read a => Int -> ReadS (MediaType a)
forall a. Read a => ReadS [MediaType a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MediaType a]
$creadListPrec :: forall a. Read a => ReadPrec [MediaType a]
readPrec :: ReadPrec (MediaType a)
$creadPrec :: forall a. Read a => ReadPrec (MediaType a)
readList :: ReadS [MediaType a]
$creadList :: forall a. Read a => ReadS [MediaType a]
readsPrec :: Int -> ReadS (MediaType a)
$creadsPrec :: forall a. Read a => Int -> ReadS (MediaType a)
Read, Int -> MediaType a -> ShowS
forall a. Show a => Int -> MediaType a -> ShowS
forall a. Show a => [MediaType a] -> ShowS
forall a. Show a => MediaType a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MediaType a] -> ShowS
$cshowList :: forall a. Show a => [MediaType a] -> ShowS
show :: MediaType a -> String
$cshow :: forall a. Show a => MediaType a -> String
showsPrec :: Int -> MediaType a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> MediaType a -> ShowS
Show, Typeable, MediaType a -> DataType
MediaType a -> Constr
forall {a}. Data a => Typeable (MediaType a)
forall a. Data a => MediaType a -> DataType
forall a. Data a => MediaType a -> Constr
forall a.
Data a =>
(forall b. Data b => b -> b) -> MediaType a -> MediaType a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> MediaType a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> MediaType a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MediaType a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MediaType a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> MediaType a -> m (MediaType a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> MediaType a -> m (MediaType a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (MediaType a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MediaType a -> c (MediaType a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (MediaType a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (MediaType a))
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 (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (MediaType a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MediaType a -> c (MediaType a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (MediaType a))
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MediaType a -> m (MediaType a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> MediaType a -> m (MediaType a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MediaType a -> m (MediaType a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> MediaType a -> m (MediaType a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MediaType a -> m (MediaType a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> MediaType a -> m (MediaType a)
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MediaType a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> MediaType a -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> MediaType a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> MediaType a -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MediaType a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MediaType a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MediaType a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MediaType a -> r
gmapT :: (forall b. Data b => b -> b) -> MediaType a -> MediaType a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> MediaType a -> MediaType a
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (MediaType a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (MediaType a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (MediaType a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (MediaType a))
dataTypeOf :: MediaType a -> DataType
$cdataTypeOf :: forall a. Data a => MediaType a -> DataType
toConstr :: MediaType a -> Constr
$ctoConstr :: forall a. Data a => MediaType a -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (MediaType a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (MediaType a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MediaType a -> c (MediaType a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MediaType a -> c (MediaType a)
Data, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (MediaType a) x -> MediaType a
forall a x. MediaType a -> Rep (MediaType a) x
$cto :: forall a x. Rep (MediaType a) x -> MediaType a
$cfrom :: forall a x. MediaType a -> Rep (MediaType a) x
Generic)
data RW
= RO
| RA
| RW
deriving (RW -> RW -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RW -> RW -> Bool
$c/= :: RW -> RW -> Bool
== :: RW -> RW -> Bool
$c== :: RW -> RW -> Bool
Eq, Eq RW
RW -> RW -> Bool
RW -> RW -> Ordering
RW -> RW -> RW
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 :: RW -> RW -> RW
$cmin :: RW -> RW -> RW
max :: RW -> RW -> RW
$cmax :: RW -> RW -> RW
>= :: RW -> RW -> Bool
$c>= :: RW -> RW -> Bool
> :: RW -> RW -> Bool
$c> :: RW -> RW -> Bool
<= :: RW -> RW -> Bool
$c<= :: RW -> RW -> Bool
< :: RW -> RW -> Bool
$c< :: RW -> RW -> Bool
compare :: RW -> RW -> Ordering
$ccompare :: RW -> RW -> Ordering
Ord, ReadPrec [RW]
ReadPrec RW
Int -> ReadS RW
ReadS [RW]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RW]
$creadListPrec :: ReadPrec [RW]
readPrec :: ReadPrec RW
$creadPrec :: ReadPrec RW
readList :: ReadS [RW]
$creadList :: ReadS [RW]
readsPrec :: Int -> ReadS RW
$creadsPrec :: Int -> ReadS RW
Read, Int -> RW -> ShowS
[RW] -> ShowS
RW -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RW] -> ShowS
$cshowList :: [RW] -> ShowS
show :: RW -> String
$cshow :: RW -> String
showsPrec :: Int -> RW -> ShowS
$cshowsPrec :: Int -> RW -> ShowS
Show, Int -> RW
RW -> Int
RW -> [RW]
RW -> RW
RW -> RW -> [RW]
RW -> RW -> RW -> [RW]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: RW -> RW -> RW -> [RW]
$cenumFromThenTo :: RW -> RW -> RW -> [RW]
enumFromTo :: RW -> RW -> [RW]
$cenumFromTo :: RW -> RW -> [RW]
enumFromThen :: RW -> RW -> [RW]
$cenumFromThen :: RW -> RW -> [RW]
enumFrom :: RW -> [RW]
$cenumFrom :: RW -> [RW]
fromEnum :: RW -> Int
$cfromEnum :: RW -> Int
toEnum :: Int -> RW
$ctoEnum :: Int -> RW
pred :: RW -> RW
$cpred :: RW -> RW
succ :: RW -> RW
$csucc :: RW -> RW
Enum, RW
forall a. a -> a -> Bounded a
maxBound :: RW
$cmaxBound :: RW
minBound :: RW
$cminBound :: RW
Bounded, Typeable, Typeable RW
RW -> DataType
RW -> Constr
(forall b. Data b => b -> b) -> RW -> RW
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) -> RW -> u
forall u. (forall d. Data d => d -> u) -> RW -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RW -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RW -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RW -> m RW
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RW -> m RW
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RW
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RW -> c RW
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RW)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RW)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RW -> m RW
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RW -> m RW
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RW -> m RW
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RW -> m RW
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RW -> m RW
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RW -> m RW
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RW -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RW -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> RW -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RW -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RW -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RW -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RW -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RW -> r
gmapT :: (forall b. Data b => b -> b) -> RW -> RW
$cgmapT :: (forall b. Data b => b -> b) -> RW -> RW
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RW)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RW)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RW)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RW)
dataTypeOf :: RW -> DataType
$cdataTypeOf :: RW -> DataType
toConstr :: RW -> Constr
$ctoConstr :: RW -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RW
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RW
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RW -> c RW
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RW -> c RW
Data, forall x. Rep RW x -> RW
forall x. RW -> Rep RW x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RW x -> RW
$cfrom :: forall x. RW -> Rep RW x
Generic)
data GenRequest (mt :: MediaType *) (rw :: RW) a where
Query :: Paths -> QueryString -> GenRequest mt rw a
PagedQuery :: (a ~ t b, Foldable t, Semigroup a) => Paths -> QueryString -> FetchCount -> GenRequest mt rw a
Command
:: CommandMethod
-> Paths
-> LBS.ByteString
-> GenRequest mt 'RW a
deriving (Typeable)
type Request = GenRequest 'MtJSON
query :: Paths -> QueryString -> Request mt a
query :: forall (mt :: RW) a. Paths -> QueryString -> Request mt a
query Paths
ps QueryString
qs = forall (mt :: MediaType (*)) (rw :: RW) a.
Paths -> QueryString -> GenRequest mt rw a
Query Paths
ps QueryString
qs
pagedQuery :: FromJSON a => Paths -> QueryString -> FetchCount -> Request mt (Vector a)
pagedQuery :: forall a (mt :: RW).
FromJSON a =>
Paths -> QueryString -> FetchCount -> Request mt (Vector a)
pagedQuery Paths
ps QueryString
qs FetchCount
fc = forall a (t :: * -> *) b (mt :: MediaType (*)) (rw :: RW).
(a ~ t b, Foldable t, Semigroup a) =>
Paths -> QueryString -> FetchCount -> GenRequest mt rw a
PagedQuery Paths
ps QueryString
qs FetchCount
fc
command :: CommandMethod -> Paths -> LBS.ByteString -> Request 'RW a
command :: forall a. CommandMethod -> Paths -> ByteString -> Request 'RW a
command CommandMethod
m Paths
ps ByteString
body = forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
m Paths
ps ByteString
body
deriving instance Eq (GenRequest rw mt a)
deriving instance Ord (GenRequest rw mt a)
deriving instance Show (GenRequest rw mt a)
instance Hashable (GenRequest rw mt a) where
hashWithSalt :: Int -> GenRequest rw mt a -> Int
hashWithSalt Int
salt (Query Paths
ps QueryString
qs) =
Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` (Int
0 :: Int)
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Paths
ps
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` QueryString
qs
hashWithSalt Int
salt (PagedQuery Paths
ps QueryString
qs FetchCount
l) =
Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` (Int
1 :: Int)
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Paths
ps
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` QueryString
qs
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` FetchCount
l
hashWithSalt Int
salt (Command CommandMethod
m Paths
ps ByteString
body) =
Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` (Int
2 :: Int)
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` CommandMethod
m
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Paths
ps
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` ByteString
body