{-# 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 = Name a -> Text
forall a. Name a -> Text
untagName
instance IsPathPart (Id a) where
toPathPart :: Id a -> Text
toPathPart = String -> Text
T.pack (String -> Text) -> (Id a -> String) -> Id a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show (Int -> String) -> (Id a -> Int) -> Id a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Id a -> Int
forall entity. Id entity -> Int
untagId
instance IsPathPart IssueNumber where
toPathPart :: IssueNumber -> Text
toPathPart = String -> Text
T.pack (String -> Text) -> (IssueNumber -> String) -> IssueNumber -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show (Int -> String) -> (IssueNumber -> Int) -> IssueNumber -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IssueNumber -> Int
unIssueNumber
data CommandMethod
= Post
| Patch
| Put
| Delete
deriving (CommandMethod -> CommandMethod -> Bool
(CommandMethod -> CommandMethod -> Bool)
-> (CommandMethod -> CommandMethod -> Bool) -> Eq CommandMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CommandMethod -> CommandMethod -> Bool
== :: CommandMethod -> CommandMethod -> Bool
$c/= :: CommandMethod -> CommandMethod -> Bool
/= :: CommandMethod -> CommandMethod -> Bool
Eq, Eq CommandMethod
Eq CommandMethod =>
(CommandMethod -> CommandMethod -> Ordering)
-> (CommandMethod -> CommandMethod -> Bool)
-> (CommandMethod -> CommandMethod -> Bool)
-> (CommandMethod -> CommandMethod -> Bool)
-> (CommandMethod -> CommandMethod -> Bool)
-> (CommandMethod -> CommandMethod -> CommandMethod)
-> (CommandMethod -> CommandMethod -> CommandMethod)
-> Ord 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
$ccompare :: CommandMethod -> CommandMethod -> Ordering
compare :: CommandMethod -> CommandMethod -> Ordering
$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
>= :: CommandMethod -> CommandMethod -> Bool
$cmax :: CommandMethod -> CommandMethod -> CommandMethod
max :: CommandMethod -> CommandMethod -> CommandMethod
$cmin :: CommandMethod -> CommandMethod -> CommandMethod
min :: CommandMethod -> CommandMethod -> CommandMethod
Ord, ReadPrec [CommandMethod]
ReadPrec CommandMethod
Int -> ReadS CommandMethod
ReadS [CommandMethod]
(Int -> ReadS CommandMethod)
-> ReadS [CommandMethod]
-> ReadPrec CommandMethod
-> ReadPrec [CommandMethod]
-> Read CommandMethod
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CommandMethod
readsPrec :: Int -> ReadS CommandMethod
$creadList :: ReadS [CommandMethod]
readList :: ReadS [CommandMethod]
$creadPrec :: ReadPrec CommandMethod
readPrec :: ReadPrec CommandMethod
$creadListPrec :: ReadPrec [CommandMethod]
readListPrec :: ReadPrec [CommandMethod]
Read, Int -> CommandMethod -> ShowS
[CommandMethod] -> ShowS
CommandMethod -> String
(Int -> CommandMethod -> ShowS)
-> (CommandMethod -> String)
-> ([CommandMethod] -> ShowS)
-> Show CommandMethod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CommandMethod -> ShowS
showsPrec :: Int -> CommandMethod -> ShowS
$cshow :: CommandMethod -> String
show :: CommandMethod -> String
$cshowList :: [CommandMethod] -> ShowS
showList :: [CommandMethod] -> ShowS
Show, Int -> CommandMethod
CommandMethod -> Int
CommandMethod -> [CommandMethod]
CommandMethod -> CommandMethod
CommandMethod -> CommandMethod -> [CommandMethod]
CommandMethod -> CommandMethod -> CommandMethod -> [CommandMethod]
(CommandMethod -> CommandMethod)
-> (CommandMethod -> CommandMethod)
-> (Int -> CommandMethod)
-> (CommandMethod -> Int)
-> (CommandMethod -> [CommandMethod])
-> (CommandMethod -> CommandMethod -> [CommandMethod])
-> (CommandMethod -> CommandMethod -> [CommandMethod])
-> (CommandMethod
-> CommandMethod -> CommandMethod -> [CommandMethod])
-> Enum 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
$csucc :: CommandMethod -> CommandMethod
succ :: CommandMethod -> CommandMethod
$cpred :: CommandMethod -> CommandMethod
pred :: CommandMethod -> CommandMethod
$ctoEnum :: Int -> CommandMethod
toEnum :: Int -> CommandMethod
$cfromEnum :: CommandMethod -> Int
fromEnum :: CommandMethod -> Int
$cenumFrom :: CommandMethod -> [CommandMethod]
enumFrom :: CommandMethod -> [CommandMethod]
$cenumFromThen :: CommandMethod -> CommandMethod -> [CommandMethod]
enumFromThen :: CommandMethod -> CommandMethod -> [CommandMethod]
$cenumFromTo :: CommandMethod -> CommandMethod -> [CommandMethod]
enumFromTo :: CommandMethod -> CommandMethod -> [CommandMethod]
$cenumFromThenTo :: CommandMethod -> CommandMethod -> CommandMethod -> [CommandMethod]
enumFromThenTo :: CommandMethod -> CommandMethod -> CommandMethod -> [CommandMethod]
Enum, CommandMethod
CommandMethod -> CommandMethod -> Bounded CommandMethod
forall a. a -> a -> Bounded a
$cminBound :: CommandMethod
minBound :: CommandMethod
$cmaxBound :: CommandMethod
maxBound :: CommandMethod
Bounded, Typeable, Typeable CommandMethod
Typeable CommandMethod =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CommandMethod -> c CommandMethod)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CommandMethod)
-> (CommandMethod -> Constr)
-> (CommandMethod -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> CommandMethod -> CommandMethod)
-> (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 u. (forall d. Data d => d -> u) -> CommandMethod -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CommandMethod -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CommandMethod -> m CommandMethod)
-> Data CommandMethod
CommandMethod -> Constr
CommandMethod -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CommandMethod -> c CommandMethod
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CommandMethod -> c CommandMethod
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CommandMethod
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CommandMethod
$ctoConstr :: CommandMethod -> Constr
toConstr :: CommandMethod -> Constr
$cdataTypeOf :: CommandMethod -> DataType
dataTypeOf :: CommandMethod -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CommandMethod)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CommandMethod)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CommandMethod)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CommandMethod)
$cgmapT :: (forall b. Data b => b -> b) -> CommandMethod -> CommandMethod
gmapT :: (forall b. Data b => b -> b) -> CommandMethod -> CommandMethod
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CommandMethod -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CommandMethod -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> CommandMethod -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CommandMethod -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CommandMethod -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CommandMethod -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CommandMethod -> m CommandMethod
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CommandMethod -> m CommandMethod
Data, (forall x. CommandMethod -> Rep CommandMethod x)
-> (forall x. Rep CommandMethod x -> CommandMethod)
-> Generic CommandMethod
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
$cfrom :: forall x. CommandMethod -> Rep CommandMethod x
from :: forall x. CommandMethod -> Rep CommandMethod x
$cto :: forall x. Rep CommandMethod x -> CommandMethod
to :: forall x. Rep CommandMethod x -> CommandMethod
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
(FetchCount -> FetchCount -> Bool)
-> (FetchCount -> FetchCount -> Bool) -> Eq FetchCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FetchCount -> FetchCount -> Bool
== :: FetchCount -> FetchCount -> Bool
$c/= :: FetchCount -> FetchCount -> Bool
/= :: FetchCount -> FetchCount -> Bool
Eq, Eq FetchCount
Eq FetchCount =>
(FetchCount -> FetchCount -> Ordering)
-> (FetchCount -> FetchCount -> Bool)
-> (FetchCount -> FetchCount -> Bool)
-> (FetchCount -> FetchCount -> Bool)
-> (FetchCount -> FetchCount -> Bool)
-> (FetchCount -> FetchCount -> FetchCount)
-> (FetchCount -> FetchCount -> FetchCount)
-> Ord 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
$ccompare :: FetchCount -> FetchCount -> Ordering
compare :: FetchCount -> FetchCount -> Ordering
$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
>= :: FetchCount -> FetchCount -> Bool
$cmax :: FetchCount -> FetchCount -> FetchCount
max :: FetchCount -> FetchCount -> FetchCount
$cmin :: FetchCount -> FetchCount -> FetchCount
min :: FetchCount -> FetchCount -> FetchCount
Ord, ReadPrec [FetchCount]
ReadPrec FetchCount
Int -> ReadS FetchCount
ReadS [FetchCount]
(Int -> ReadS FetchCount)
-> ReadS [FetchCount]
-> ReadPrec FetchCount
-> ReadPrec [FetchCount]
-> Read FetchCount
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FetchCount
readsPrec :: Int -> ReadS FetchCount
$creadList :: ReadS [FetchCount]
readList :: ReadS [FetchCount]
$creadPrec :: ReadPrec FetchCount
readPrec :: ReadPrec FetchCount
$creadListPrec :: ReadPrec [FetchCount]
readListPrec :: ReadPrec [FetchCount]
Read, Int -> FetchCount -> ShowS
[FetchCount] -> ShowS
FetchCount -> String
(Int -> FetchCount -> ShowS)
-> (FetchCount -> String)
-> ([FetchCount] -> ShowS)
-> Show FetchCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FetchCount -> ShowS
showsPrec :: Int -> FetchCount -> ShowS
$cshow :: FetchCount -> String
show :: FetchCount -> String
$cshowList :: [FetchCount] -> ShowS
showList :: [FetchCount] -> ShowS
Show, (forall x. FetchCount -> Rep FetchCount x)
-> (forall x. Rep FetchCount x -> FetchCount) -> Generic FetchCount
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
$cfrom :: forall x. FetchCount -> Rep FetchCount x
from :: forall x. FetchCount -> Rep FetchCount x
$cto :: forall x. Rep FetchCount x -> FetchCount
to :: forall x. Rep FetchCount x -> FetchCount
Generic, Typeable)
instance Num FetchCount where
fromInteger :: Integer -> FetchCount
fromInteger = Word -> FetchCount
FetchAtLeast (Word -> FetchCount) -> (Integer -> Word) -> Integer -> FetchCount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Word
forall a. Num a => Integer -> a
fromInteger
FetchAtLeast Word
a + :: FetchCount -> FetchCount -> FetchCount
+ FetchAtLeast Word
b = Word -> FetchCount
FetchAtLeast (Word
a Word -> Word -> Word
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 Word -> Word -> Word
forall a. Num a => a -> a -> a
* Word
b)
FetchCount
_ * FetchCount
_ = FetchCount
FetchAll
abs :: FetchCount -> FetchCount
abs = String -> FetchCount -> FetchCount
forall a. HasCallStack => String -> a
error String
"abs @FetchCount: not implemented"
signum :: FetchCount -> FetchCount
signum = String -> FetchCount -> FetchCount
forall a. HasCallStack => String -> a
error String
"signum @FetchCount: not implemented"
negate :: FetchCount -> FetchCount
negate = String -> FetchCount -> FetchCount
forall a. HasCallStack => String -> a
error String
"negate @FetchCount: not implemented"
instance Hashable FetchCount
instance Binary FetchCount
instance NFData FetchCount where rnf :: FetchCount -> ()
rnf = FetchCount -> ()
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
(MediaType a -> MediaType a -> Bool)
-> (MediaType a -> MediaType a -> Bool) -> Eq (MediaType a)
forall a. Eq a => MediaType a -> MediaType a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$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
/= :: MediaType a -> MediaType a -> Bool
Eq, Eq (MediaType a)
Eq (MediaType a) =>
(MediaType a -> MediaType a -> Ordering)
-> (MediaType a -> MediaType a -> Bool)
-> (MediaType a -> MediaType a -> Bool)
-> (MediaType a -> MediaType a -> Bool)
-> (MediaType a -> MediaType a -> Bool)
-> (MediaType a -> MediaType a -> MediaType a)
-> (MediaType a -> MediaType a -> MediaType a)
-> Ord (MediaType a)
MediaType a -> MediaType a -> Bool
MediaType a -> MediaType a -> Ordering
MediaType a -> MediaType a -> MediaType a
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
$ccompare :: forall a. Ord a => MediaType a -> MediaType a -> Ordering
compare :: MediaType a -> MediaType a -> Ordering
$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
>= :: MediaType a -> MediaType a -> Bool
$cmax :: forall a. Ord a => MediaType a -> MediaType a -> MediaType a
max :: MediaType a -> MediaType a -> MediaType a
$cmin :: forall a. Ord a => MediaType a -> MediaType a -> MediaType a
min :: MediaType a -> MediaType a -> MediaType a
Ord, ReadPrec [MediaType a]
ReadPrec (MediaType a)
Int -> ReadS (MediaType a)
ReadS [MediaType a]
(Int -> ReadS (MediaType a))
-> ReadS [MediaType a]
-> ReadPrec (MediaType a)
-> ReadPrec [MediaType a]
-> Read (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
$creadsPrec :: forall a. Read a => Int -> ReadS (MediaType a)
readsPrec :: Int -> ReadS (MediaType a)
$creadList :: forall a. Read a => ReadS [MediaType a]
readList :: ReadS [MediaType a]
$creadPrec :: forall a. Read a => ReadPrec (MediaType a)
readPrec :: ReadPrec (MediaType a)
$creadListPrec :: forall a. Read a => ReadPrec [MediaType a]
readListPrec :: ReadPrec [MediaType a]
Read, Int -> MediaType a -> ShowS
[MediaType a] -> ShowS
MediaType a -> String
(Int -> MediaType a -> ShowS)
-> (MediaType a -> String)
-> ([MediaType a] -> ShowS)
-> Show (MediaType a)
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
$cshowsPrec :: forall a. Show a => Int -> MediaType a -> ShowS
showsPrec :: Int -> MediaType a -> ShowS
$cshow :: forall a. Show a => MediaType a -> String
show :: MediaType a -> String
$cshowList :: forall a. Show a => [MediaType a] -> ShowS
showList :: [MediaType a] -> ShowS
Show, Typeable, Typeable (MediaType a)
Typeable (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 (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (MediaType a))
-> (MediaType a -> Constr)
-> (MediaType a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (MediaType a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (MediaType a)))
-> ((forall b. Data b => b -> b) -> MediaType a -> MediaType a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MediaType a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MediaType a -> r)
-> (forall u. (forall d. Data d => d -> u) -> MediaType a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> MediaType a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MediaType a -> m (MediaType a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MediaType a -> m (MediaType a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MediaType a -> m (MediaType a))
-> Data (MediaType a)
MediaType a -> Constr
MediaType a -> DataType
(forall b. Data b => b -> b) -> MediaType a -> MediaType a
forall a. Data a => Typeable (MediaType a)
forall a. Data a => MediaType a -> Constr
forall a. Data a => MediaType a -> DataType
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 u. Int -> (forall d. Data d => d -> u) -> MediaType a -> u
forall u. (forall d. Data d => d -> u) -> MediaType a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MediaType a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MediaType a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MediaType a -> m (MediaType a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MediaType a -> m (MediaType 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))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (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)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MediaType a -> 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)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (MediaType a)
$ctoConstr :: forall a. Data a => MediaType a -> Constr
toConstr :: MediaType a -> Constr
$cdataTypeOf :: forall a. Data a => MediaType a -> DataType
dataTypeOf :: MediaType a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (MediaType a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> 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))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (MediaType a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> MediaType a -> MediaType a
gmapT :: (forall b. Data b => b -> b) -> MediaType a -> MediaType a
$cgmapQl :: 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
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MediaType a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MediaType a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> MediaType a -> [u]
gmapQ :: forall u. (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
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MediaType a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad 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)
$cgmapMp :: 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)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> MediaType a -> m (MediaType a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MediaType a -> m (MediaType a)
Data, (forall x. MediaType a -> Rep (MediaType a) x)
-> (forall x. Rep (MediaType a) x -> MediaType a)
-> Generic (MediaType a)
forall x. Rep (MediaType a) x -> MediaType a
forall x. MediaType a -> Rep (MediaType a) x
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
$cfrom :: forall a x. MediaType a -> Rep (MediaType a) x
from :: forall x. MediaType a -> Rep (MediaType a) x
$cto :: forall a x. Rep (MediaType a) x -> MediaType a
to :: forall x. Rep (MediaType a) x -> MediaType a
Generic)
data RW
= RO
| RA
| RW
deriving (RW -> RW -> Bool
(RW -> RW -> Bool) -> (RW -> RW -> Bool) -> Eq RW
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RW -> RW -> Bool
== :: RW -> RW -> Bool
$c/= :: RW -> RW -> Bool
/= :: RW -> RW -> Bool
Eq, Eq RW
Eq RW =>
(RW -> RW -> Ordering)
-> (RW -> RW -> Bool)
-> (RW -> RW -> Bool)
-> (RW -> RW -> Bool)
-> (RW -> RW -> Bool)
-> (RW -> RW -> RW)
-> (RW -> RW -> RW)
-> Ord 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
$ccompare :: RW -> RW -> Ordering
compare :: RW -> RW -> Ordering
$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
>= :: RW -> RW -> Bool
$cmax :: RW -> RW -> RW
max :: RW -> RW -> RW
$cmin :: RW -> RW -> RW
min :: RW -> RW -> RW
Ord, ReadPrec [RW]
ReadPrec RW
Int -> ReadS RW
ReadS [RW]
(Int -> ReadS RW)
-> ReadS [RW] -> ReadPrec RW -> ReadPrec [RW] -> Read RW
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RW
readsPrec :: Int -> ReadS RW
$creadList :: ReadS [RW]
readList :: ReadS [RW]
$creadPrec :: ReadPrec RW
readPrec :: ReadPrec RW
$creadListPrec :: ReadPrec [RW]
readListPrec :: ReadPrec [RW]
Read, Int -> RW -> ShowS
[RW] -> ShowS
RW -> String
(Int -> RW -> ShowS)
-> (RW -> String) -> ([RW] -> ShowS) -> Show RW
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RW -> ShowS
showsPrec :: Int -> RW -> ShowS
$cshow :: RW -> String
show :: RW -> String
$cshowList :: [RW] -> ShowS
showList :: [RW] -> ShowS
Show, Int -> RW
RW -> Int
RW -> [RW]
RW -> RW
RW -> RW -> [RW]
RW -> RW -> RW -> [RW]
(RW -> RW)
-> (RW -> RW)
-> (Int -> RW)
-> (RW -> Int)
-> (RW -> [RW])
-> (RW -> RW -> [RW])
-> (RW -> RW -> [RW])
-> (RW -> RW -> RW -> [RW])
-> Enum 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
$csucc :: RW -> RW
succ :: RW -> RW
$cpred :: RW -> RW
pred :: RW -> RW
$ctoEnum :: Int -> RW
toEnum :: Int -> RW
$cfromEnum :: RW -> Int
fromEnum :: RW -> Int
$cenumFrom :: RW -> [RW]
enumFrom :: RW -> [RW]
$cenumFromThen :: RW -> RW -> [RW]
enumFromThen :: RW -> RW -> [RW]
$cenumFromTo :: RW -> RW -> [RW]
enumFromTo :: RW -> RW -> [RW]
$cenumFromThenTo :: RW -> RW -> RW -> [RW]
enumFromThenTo :: RW -> RW -> RW -> [RW]
Enum, RW
RW -> RW -> Bounded RW
forall a. a -> a -> Bounded a
$cminBound :: RW
minBound :: RW
$cmaxBound :: RW
maxBound :: RW
Bounded, Typeable, Typeable RW
Typeable RW =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RW -> c RW)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RW)
-> (RW -> Constr)
-> (RW -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> RW -> RW)
-> (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 u. (forall d. Data d => d -> u) -> RW -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> RW -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RW -> m RW)
-> Data RW
RW -> Constr
RW -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RW -> c RW
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RW -> c RW
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RW
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RW
$ctoConstr :: RW -> Constr
toConstr :: RW -> Constr
$cdataTypeOf :: RW -> DataType
dataTypeOf :: RW -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RW)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RW)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RW)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RW)
$cgmapT :: (forall b. Data b => b -> b) -> RW -> RW
gmapT :: (forall b. Data b => b -> b) -> RW -> RW
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RW -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RW -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RW -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> RW -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RW -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RW -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RW -> m RW
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RW -> m RW
Data, (forall x. RW -> Rep RW x)
-> (forall x. Rep RW x -> RW) -> Generic RW
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
$cfrom :: forall x. RW -> Rep RW x
from :: forall x. RW -> Rep RW x
$cto :: forall x. Rep RW x -> RW
to :: forall x. Rep RW x -> RW
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 = Paths -> QueryString -> GenRequest 'MtJSON mt a
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 = Paths
-> QueryString -> FetchCount -> GenRequest 'MtJSON mt (Vector a)
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 = CommandMethod -> Paths -> ByteString -> GenRequest 'MtJSON 'RW a
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 Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` (Int
0 :: Int)
Int -> Paths -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Paths
ps
Int -> QueryString -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` QueryString
qs
hashWithSalt Int
salt (PagedQuery Paths
ps QueryString
qs FetchCount
l) =
Int
salt Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` (Int
1 :: Int)
Int -> Paths -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Paths
ps
Int -> QueryString -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` QueryString
qs
Int -> FetchCount -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` FetchCount
l
hashWithSalt Int
salt (Command CommandMethod
m Paths
ps ByteString
body) =
Int
salt Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` (Int
2 :: Int)
Int -> CommandMethod -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` CommandMethod
m
Int -> Paths -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Paths
ps
Int -> ByteString -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` ByteString
body