{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-unused-binds -fno-warn-unused-imports #-}
module OryHydra.Core where
import OryHydra.MimeTypes
import OryHydra.Logging
import qualified Control.Arrow as P (left)
import qualified Control.DeepSeq as NF
import qualified Control.Exception.Safe as E
import qualified Data.Aeson as A
import qualified Data.ByteString as B
import qualified Data.ByteString.Base64.Lazy as BL64
import qualified Data.ByteString.Builder as BB
import qualified Data.ByteString.Char8 as BC
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BCL
import qualified Data.CaseInsensitive as CI
import qualified Data.Data as P (Data, Typeable, TypeRep, typeRep)
import qualified Data.Foldable as P
import qualified Data.Ix as P
import qualified Data.Kind as K (Type)
import qualified Data.Maybe as P
import qualified Data.Proxy as P (Proxy(..))
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Time as TI
import qualified Data.Time.ISO8601 as TI
import qualified GHC.Base as P (Alternative)
import qualified Lens.Micro as L
import qualified Network.HTTP.Client.MultipartFormData as NH
import qualified Network.HTTP.Types as NH
import qualified Prelude as P
import qualified Text.Printf as T
import qualified Web.FormUrlEncoded as WH
import qualified Web.HttpApiData as WH
import Control.Applicative ((<|>))
import Control.Applicative (Alternative)
import Control.Monad.Fail (MonadFail)
import Data.Function ((&))
import Data.Foldable(foldlM)
import Data.Monoid ((<>))
import Data.Text (Text)
import Prelude (($), (.), (&&), (<$>), (<*>), Maybe(..), Bool(..), Char, String, fmap, mempty, pure, return, show, IO, Monad, Functor, maybe)
data OryHydraConfig = OryHydraConfig
{ OryHydraConfig -> ByteString
configHost :: BCL.ByteString
, OryHydraConfig -> Text
configUserAgent :: Text
, OryHydraConfig -> LogExecWithContext
configLogExecWithContext :: LogExecWithContext
, OryHydraConfig -> LogContext
configLogContext :: LogContext
, OryHydraConfig -> [AnyAuthMethod]
configAuthMethods :: [AnyAuthMethod]
, OryHydraConfig -> Bool
configValidateAuthMethods :: Bool
, :: B.ByteString
}
instance P.Show OryHydraConfig where
show :: OryHydraConfig -> String
show OryHydraConfig
c =
forall r. PrintfType r => String -> r
T.printf
String
"{ configHost = %v, configUserAgent = %v, ..}"
(forall a. Show a => a -> String
show (OryHydraConfig -> ByteString
configHost OryHydraConfig
c))
(forall a. Show a => a -> String
show (OryHydraConfig -> Text
configUserAgent OryHydraConfig
c))
newConfig :: IO OryHydraConfig
newConfig :: IO OryHydraConfig
newConfig = do
LogContext
logCxt <- IO LogContext
initLogContext
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ OryHydraConfig
{ configHost :: ByteString
configHost = ByteString
"http://localhost"
, configUserAgent :: Text
configUserAgent = Text
"ory-hydra-client/0.1.0.0"
, configLogExecWithContext :: LogExecWithContext
configLogExecWithContext = LogExecWithContext
runDefaultLogExecWithContext
, configLogContext :: LogContext
configLogContext = LogContext
logCxt
, configAuthMethods :: [AnyAuthMethod]
configAuthMethods = []
, configValidateAuthMethods :: Bool
configValidateAuthMethods = Bool
True
, configQueryExtraUnreserved :: ByteString
configQueryExtraUnreserved = ByteString
""
}
addAuthMethod :: AuthMethod auth => OryHydraConfig -> auth -> OryHydraConfig
addAuthMethod :: forall auth.
AuthMethod auth =>
OryHydraConfig -> auth -> OryHydraConfig
addAuthMethod config :: OryHydraConfig
config@OryHydraConfig {configAuthMethods :: OryHydraConfig -> [AnyAuthMethod]
configAuthMethods = [AnyAuthMethod]
as} auth
a =
OryHydraConfig
config { configAuthMethods :: [AnyAuthMethod]
configAuthMethods = forall a. AuthMethod a => a -> AnyAuthMethod
AnyAuthMethod auth
a forall a. a -> [a] -> [a]
: [AnyAuthMethod]
as}
withStdoutLogging :: OryHydraConfig -> IO OryHydraConfig
withStdoutLogging :: OryHydraConfig -> IO OryHydraConfig
withStdoutLogging OryHydraConfig
p = do
LogContext
logCxt <- LogContext -> IO LogContext
stdoutLoggingContext (OryHydraConfig -> LogContext
configLogContext OryHydraConfig
p)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ OryHydraConfig
p { configLogExecWithContext :: LogExecWithContext
configLogExecWithContext = LogExecWithContext
stdoutLoggingExec, configLogContext :: LogContext
configLogContext = LogContext
logCxt }
withStderrLogging :: OryHydraConfig -> IO OryHydraConfig
withStderrLogging :: OryHydraConfig -> IO OryHydraConfig
withStderrLogging OryHydraConfig
p = do
LogContext
logCxt <- LogContext -> IO LogContext
stderrLoggingContext (OryHydraConfig -> LogContext
configLogContext OryHydraConfig
p)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ OryHydraConfig
p { configLogExecWithContext :: LogExecWithContext
configLogExecWithContext = LogExecWithContext
stderrLoggingExec, configLogContext :: LogContext
configLogContext = LogContext
logCxt }
withNoLogging :: OryHydraConfig -> OryHydraConfig
withNoLogging :: OryHydraConfig -> OryHydraConfig
withNoLogging OryHydraConfig
p = OryHydraConfig
p { configLogExecWithContext :: LogExecWithContext
configLogExecWithContext = LogExecWithContext
runNullLogExec}
data OryHydraRequest req contentType res accept = OryHydraRequest
{ forall req contentType res accept.
OryHydraRequest req contentType res accept -> ByteString
rMethod :: NH.Method
, forall req contentType res accept.
OryHydraRequest req contentType res accept -> [ByteString]
rUrlPath :: [BCL.ByteString]
, forall req contentType res accept.
OryHydraRequest req contentType res accept -> Params
rParams :: Params
, forall req contentType res accept.
OryHydraRequest req contentType res accept -> [TypeRep]
rAuthTypes :: [P.TypeRep]
}
deriving (Int -> OryHydraRequest req contentType res accept -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall req contentType res accept.
Int -> OryHydraRequest req contentType res accept -> ShowS
forall req contentType res accept.
[OryHydraRequest req contentType res accept] -> ShowS
forall req contentType res accept.
OryHydraRequest req contentType res accept -> String
showList :: [OryHydraRequest req contentType res accept] -> ShowS
$cshowList :: forall req contentType res accept.
[OryHydraRequest req contentType res accept] -> ShowS
show :: OryHydraRequest req contentType res accept -> String
$cshow :: forall req contentType res accept.
OryHydraRequest req contentType res accept -> String
showsPrec :: Int -> OryHydraRequest req contentType res accept -> ShowS
$cshowsPrec :: forall req contentType res accept.
Int -> OryHydraRequest req contentType res accept -> ShowS
P.Show)
rMethodL :: Lens_' (OryHydraRequest req contentType res accept) NH.Method
rMethodL :: forall req contentType res accept.
Lens_' (OryHydraRequest req contentType res accept) ByteString
rMethodL ByteString -> f ByteString
f OryHydraRequest{[TypeRep]
[ByteString]
ByteString
Params
rAuthTypes :: [TypeRep]
rParams :: Params
rUrlPath :: [ByteString]
rMethod :: ByteString
rAuthTypes :: forall req contentType res accept.
OryHydraRequest req contentType res accept -> [TypeRep]
rParams :: forall req contentType res accept.
OryHydraRequest req contentType res accept -> Params
rUrlPath :: forall req contentType res accept.
OryHydraRequest req contentType res accept -> [ByteString]
rMethod :: forall req contentType res accept.
OryHydraRequest req contentType res accept -> ByteString
..} = (\ByteString
rMethod -> OryHydraRequest { ByteString
rMethod :: ByteString
rMethod :: ByteString
rMethod, [TypeRep]
[ByteString]
Params
rAuthTypes :: [TypeRep]
rParams :: Params
rUrlPath :: [ByteString]
rAuthTypes :: [TypeRep]
rParams :: Params
rUrlPath :: [ByteString]
..} ) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> f ByteString
f ByteString
rMethod
{-# INLINE rMethodL #-}
rUrlPathL :: Lens_' (OryHydraRequest req contentType res accept) [BCL.ByteString]
rUrlPathL :: forall req contentType res accept.
Lens_' (OryHydraRequest req contentType res accept) [ByteString]
rUrlPathL [ByteString] -> f [ByteString]
f OryHydraRequest{[TypeRep]
[ByteString]
ByteString
Params
rAuthTypes :: [TypeRep]
rParams :: Params
rUrlPath :: [ByteString]
rMethod :: ByteString
rAuthTypes :: forall req contentType res accept.
OryHydraRequest req contentType res accept -> [TypeRep]
rParams :: forall req contentType res accept.
OryHydraRequest req contentType res accept -> Params
rUrlPath :: forall req contentType res accept.
OryHydraRequest req contentType res accept -> [ByteString]
rMethod :: forall req contentType res accept.
OryHydraRequest req contentType res accept -> ByteString
..} = (\[ByteString]
rUrlPath -> OryHydraRequest { [ByteString]
rUrlPath :: [ByteString]
rUrlPath :: [ByteString]
rUrlPath, [TypeRep]
ByteString
Params
rAuthTypes :: [TypeRep]
rParams :: Params
rMethod :: ByteString
rAuthTypes :: [TypeRep]
rParams :: Params
rMethod :: ByteString
..} ) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ByteString] -> f [ByteString]
f [ByteString]
rUrlPath
{-# INLINE rUrlPathL #-}
rParamsL :: Lens_' (OryHydraRequest req contentType res accept) Params
rParamsL :: forall req contentType res accept.
Lens_' (OryHydraRequest req contentType res accept) Params
rParamsL Params -> f Params
f OryHydraRequest{[TypeRep]
[ByteString]
ByteString
Params
rAuthTypes :: [TypeRep]
rParams :: Params
rUrlPath :: [ByteString]
rMethod :: ByteString
rAuthTypes :: forall req contentType res accept.
OryHydraRequest req contentType res accept -> [TypeRep]
rParams :: forall req contentType res accept.
OryHydraRequest req contentType res accept -> Params
rUrlPath :: forall req contentType res accept.
OryHydraRequest req contentType res accept -> [ByteString]
rMethod :: forall req contentType res accept.
OryHydraRequest req contentType res accept -> ByteString
..} = (\Params
rParams -> OryHydraRequest { Params
rParams :: Params
rParams :: Params
rParams, [TypeRep]
[ByteString]
ByteString
rAuthTypes :: [TypeRep]
rUrlPath :: [ByteString]
rMethod :: ByteString
rAuthTypes :: [TypeRep]
rUrlPath :: [ByteString]
rMethod :: ByteString
..} ) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Params -> f Params
f Params
rParams
{-# INLINE rParamsL #-}
rAuthTypesL :: Lens_' (OryHydraRequest req contentType res accept) [P.TypeRep]
rAuthTypesL :: forall req contentType res accept.
Lens_' (OryHydraRequest req contentType res accept) [TypeRep]
rAuthTypesL [TypeRep] -> f [TypeRep]
f OryHydraRequest{[TypeRep]
[ByteString]
ByteString
Params
rAuthTypes :: [TypeRep]
rParams :: Params
rUrlPath :: [ByteString]
rMethod :: ByteString
rAuthTypes :: forall req contentType res accept.
OryHydraRequest req contentType res accept -> [TypeRep]
rParams :: forall req contentType res accept.
OryHydraRequest req contentType res accept -> Params
rUrlPath :: forall req contentType res accept.
OryHydraRequest req contentType res accept -> [ByteString]
rMethod :: forall req contentType res accept.
OryHydraRequest req contentType res accept -> ByteString
..} = (\[TypeRep]
rAuthTypes -> OryHydraRequest { [TypeRep]
rAuthTypes :: [TypeRep]
rAuthTypes :: [TypeRep]
rAuthTypes, [ByteString]
ByteString
Params
rParams :: Params
rUrlPath :: [ByteString]
rMethod :: ByteString
rParams :: Params
rUrlPath :: [ByteString]
rMethod :: ByteString
..} ) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TypeRep] -> f [TypeRep]
f [TypeRep]
rAuthTypes
{-# INLINE rAuthTypesL #-}
class HasBodyParam req param where
setBodyParam :: forall contentType res accept. (Consumes req contentType, MimeRender contentType param) => OryHydraRequest req contentType res accept -> param -> OryHydraRequest req contentType res accept
setBodyParam OryHydraRequest req contentType res accept
req param
xs =
OryHydraRequest req contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> ByteString -> OryHydraRequest req contentType res accept
`_setBodyLBS` forall mtype x.
MimeRender mtype x =>
Proxy mtype -> x -> ByteString
mimeRender (forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy contentType) param
xs forall a b. a -> (a -> b) -> b
& forall req contentType res accept.
MimeType contentType =>
OryHydraRequest req contentType res accept
-> OryHydraRequest req contentType res accept
_setContentTypeHeader
class HasOptionalParam req param where
{-# MINIMAL applyOptionalParam | (-&-) #-}
applyOptionalParam :: OryHydraRequest req contentType res accept -> param -> OryHydraRequest req contentType res accept
applyOptionalParam = forall req param contentType res accept.
HasOptionalParam req param =>
OryHydraRequest req contentType res accept
-> param -> OryHydraRequest req contentType res accept
(-&-)
{-# INLINE applyOptionalParam #-}
(-&-) :: OryHydraRequest req contentType res accept -> param -> OryHydraRequest req contentType res accept
(-&-) = forall req param contentType res accept.
HasOptionalParam req param =>
OryHydraRequest req contentType res accept
-> param -> OryHydraRequest req contentType res accept
applyOptionalParam
{-# INLINE (-&-) #-}
infixl 2 -&-
data Params = Params
{ Params -> Query
paramsQuery :: NH.Query
, :: NH.RequestHeaders
, Params -> ParamBody
paramsBody :: ParamBody
}
deriving (Int -> Params -> ShowS
[Params] -> ShowS
Params -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Params] -> ShowS
$cshowList :: [Params] -> ShowS
show :: Params -> String
$cshow :: Params -> String
showsPrec :: Int -> Params -> ShowS
$cshowsPrec :: Int -> Params -> ShowS
P.Show)
paramsQueryL :: Lens_' Params NH.Query
paramsQueryL :: Lens_' Params Query
paramsQueryL Query -> f Query
f Params{Query
RequestHeaders
ParamBody
paramsBody :: ParamBody
paramsHeaders :: RequestHeaders
paramsQuery :: Query
paramsBody :: Params -> ParamBody
paramsHeaders :: Params -> RequestHeaders
paramsQuery :: Params -> Query
..} = (\Query
paramsQuery -> Params { Query
paramsQuery :: Query
paramsQuery :: Query
paramsQuery, RequestHeaders
ParamBody
paramsBody :: ParamBody
paramsHeaders :: RequestHeaders
paramsBody :: ParamBody
paramsHeaders :: RequestHeaders
..} ) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Query -> f Query
f Query
paramsQuery
{-# INLINE paramsQueryL #-}
paramsHeadersL :: Lens_' Params NH.RequestHeaders
RequestHeaders -> f RequestHeaders
f Params{Query
RequestHeaders
ParamBody
paramsBody :: ParamBody
paramsHeaders :: RequestHeaders
paramsQuery :: Query
paramsBody :: Params -> ParamBody
paramsHeaders :: Params -> RequestHeaders
paramsQuery :: Params -> Query
..} = (\RequestHeaders
paramsHeaders -> Params { RequestHeaders
paramsHeaders :: RequestHeaders
paramsHeaders :: RequestHeaders
paramsHeaders, Query
ParamBody
paramsBody :: ParamBody
paramsQuery :: Query
paramsBody :: ParamBody
paramsQuery :: Query
..} ) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RequestHeaders -> f RequestHeaders
f RequestHeaders
paramsHeaders
{-# INLINE paramsHeadersL #-}
paramsBodyL :: Lens_' Params ParamBody
paramsBodyL :: Lens_' Params ParamBody
paramsBodyL ParamBody -> f ParamBody
f Params{Query
RequestHeaders
ParamBody
paramsBody :: ParamBody
paramsHeaders :: RequestHeaders
paramsQuery :: Query
paramsBody :: Params -> ParamBody
paramsHeaders :: Params -> RequestHeaders
paramsQuery :: Params -> Query
..} = (\ParamBody
paramsBody -> Params { ParamBody
paramsBody :: ParamBody
paramsBody :: ParamBody
paramsBody, Query
RequestHeaders
paramsHeaders :: RequestHeaders
paramsQuery :: Query
paramsHeaders :: RequestHeaders
paramsQuery :: Query
..} ) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParamBody -> f ParamBody
f ParamBody
paramsBody
{-# INLINE paramsBodyL #-}
data ParamBody
= ParamBodyNone
| ParamBodyB B.ByteString
| ParamBodyBL BL.ByteString
| ParamBodyFormUrlEncoded WH.Form
| ParamBodyMultipartFormData [NH.Part]
deriving (Int -> ParamBody -> ShowS
[ParamBody] -> ShowS
ParamBody -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ParamBody] -> ShowS
$cshowList :: [ParamBody] -> ShowS
show :: ParamBody -> String
$cshow :: ParamBody -> String
showsPrec :: Int -> ParamBody -> ShowS
$cshowsPrec :: Int -> ParamBody -> ShowS
P.Show)
_mkRequest :: NH.Method
-> [BCL.ByteString]
-> OryHydraRequest req contentType res accept
_mkRequest :: forall req contentType res accept.
ByteString
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest ByteString
m [ByteString]
u = forall req contentType res accept.
ByteString
-> [ByteString]
-> Params
-> [TypeRep]
-> OryHydraRequest req contentType res accept
OryHydraRequest ByteString
m [ByteString]
u Params
_mkParams []
_mkParams :: Params
_mkParams :: Params
_mkParams = Query -> RequestHeaders -> ParamBody -> Params
Params [] [] ParamBody
ParamBodyNone
setHeader ::
OryHydraRequest req contentType res accept
-> [NH.Header]
-> OryHydraRequest req contentType res accept
OryHydraRequest req contentType res accept
req RequestHeaders
header =
OryHydraRequest req contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [HeaderName] -> OryHydraRequest req contentType res accept
`removeHeader` forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.fmap forall a b. (a, b) -> a
P.fst RequestHeaders
header
forall a b. a -> (a -> b) -> b
& (forall req contentType res accept.
OryHydraRequest req contentType res accept
-> RequestHeaders -> OryHydraRequest req contentType res accept
`addHeader` RequestHeaders
header)
addHeader ::
OryHydraRequest req contentType res accept
-> [NH.Header]
-> OryHydraRequest req contentType res accept
OryHydraRequest req contentType res accept
req RequestHeaders
header = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
L.over (forall req contentType res accept.
Lens_' (OryHydraRequest req contentType res accept) Params
rParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens_' Params RequestHeaders
paramsHeadersL) (RequestHeaders
header forall a. [a] -> [a] -> [a]
P.++) OryHydraRequest req contentType res accept
req
removeHeader :: OryHydraRequest req contentType res accept -> [NH.HeaderName] -> OryHydraRequest req contentType res accept
OryHydraRequest req contentType res accept
req [HeaderName]
header =
OryHydraRequest req contentType res accept
req forall a b. a -> (a -> b) -> b
&
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
L.over
(forall req contentType res accept.
Lens_' (OryHydraRequest req contentType res accept) Params
rParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens_' Params RequestHeaders
paramsHeadersL)
(forall a. (a -> Bool) -> [a] -> [a]
P.filter (\(HeaderName, ByteString)
h -> forall {b}. (HeaderName, b) -> CI HeaderName
cifst (HeaderName, ByteString)
h forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`P.notElem` forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.fmap forall s. FoldCase s => s -> CI s
CI.mk [HeaderName]
header))
where
cifst :: (HeaderName, b) -> CI HeaderName
cifst = forall s. FoldCase s => s -> CI s
CI.mk forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
P.fst
_setContentTypeHeader :: forall req contentType res accept. MimeType contentType => OryHydraRequest req contentType res accept -> OryHydraRequest req contentType res accept
OryHydraRequest req contentType res accept
req =
case forall mtype. MimeType mtype => Proxy mtype -> Maybe MediaType
mimeType (forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy contentType) of
Just MediaType
m -> OryHydraRequest req contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> RequestHeaders -> OryHydraRequest req contentType res accept
`setHeader` [(HeaderName
"content-type", String -> ByteString
BC.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
P.show MediaType
m)]
Maybe MediaType
Nothing -> OryHydraRequest req contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [HeaderName] -> OryHydraRequest req contentType res accept
`removeHeader` [HeaderName
"content-type"]
_setAcceptHeader :: forall req contentType res accept. MimeType accept => OryHydraRequest req contentType res accept -> OryHydraRequest req contentType res accept
OryHydraRequest req contentType res accept
req =
case forall mtype. MimeType mtype => Proxy mtype -> Maybe MediaType
mimeType (forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy accept) of
Just MediaType
m -> OryHydraRequest req contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> RequestHeaders -> OryHydraRequest req contentType res accept
`setHeader` [(HeaderName
"accept", String -> ByteString
BC.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
P.show MediaType
m)]
Maybe MediaType
Nothing -> OryHydraRequest req contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [HeaderName] -> OryHydraRequest req contentType res accept
`removeHeader` [HeaderName
"accept"]
setQuery ::
OryHydraRequest req contentType res accept
-> [NH.QueryItem]
-> OryHydraRequest req contentType res accept
setQuery :: forall req contentType res accept.
OryHydraRequest req contentType res accept
-> Query -> OryHydraRequest req contentType res accept
setQuery OryHydraRequest req contentType res accept
req Query
query =
OryHydraRequest req contentType res accept
req forall a b. a -> (a -> b) -> b
&
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
L.over
(forall req contentType res accept.
Lens_' (OryHydraRequest req contentType res accept) Params
rParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens_' Params Query
paramsQueryL)
(forall a. (a -> Bool) -> [a] -> [a]
P.filter (\(ByteString, Maybe ByteString)
q -> forall {b}. (ByteString, b) -> HeaderName
cifst (ByteString, Maybe ByteString)
q forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`P.notElem` forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.fmap forall {b}. (ByteString, b) -> HeaderName
cifst Query
query)) forall a b. a -> (a -> b) -> b
&
(forall req contentType res accept.
OryHydraRequest req contentType res accept
-> Query -> OryHydraRequest req contentType res accept
`addQuery` Query
query)
where
cifst :: (ByteString, b) -> HeaderName
cifst = forall s. FoldCase s => s -> CI s
CI.mk forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
P.fst
addQuery ::
OryHydraRequest req contentType res accept
-> [NH.QueryItem]
-> OryHydraRequest req contentType res accept
addQuery :: forall req contentType res accept.
OryHydraRequest req contentType res accept
-> Query -> OryHydraRequest req contentType res accept
addQuery OryHydraRequest req contentType res accept
req Query
query = OryHydraRequest req contentType res accept
req forall a b. a -> (a -> b) -> b
& forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
L.over (forall req contentType res accept.
Lens_' (OryHydraRequest req contentType res accept) Params
rParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens_' Params Query
paramsQueryL) (Query
query forall a. [a] -> [a] -> [a]
P.++)
addForm :: OryHydraRequest req contentType res accept -> WH.Form -> OryHydraRequest req contentType res accept
addForm :: forall req contentType res accept.
OryHydraRequest req contentType res accept
-> Form -> OryHydraRequest req contentType res accept
addForm OryHydraRequest req contentType res accept
req Form
newform =
let form :: Form
form = case Params -> ParamBody
paramsBody (forall req contentType res accept.
OryHydraRequest req contentType res accept -> Params
rParams OryHydraRequest req contentType res accept
req) of
ParamBodyFormUrlEncoded Form
_form -> Form
_form
ParamBody
_ -> forall a. Monoid a => a
mempty
in OryHydraRequest req contentType res accept
req forall a b. a -> (a -> b) -> b
& forall s t a b. ASetter s t a b -> b -> s -> t
L.set (forall req contentType res accept.
Lens_' (OryHydraRequest req contentType res accept) Params
rParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens_' Params ParamBody
paramsBodyL) (Form -> ParamBody
ParamBodyFormUrlEncoded (Form
newform forall a. Semigroup a => a -> a -> a
<> Form
form))
_addMultiFormPart :: OryHydraRequest req contentType res accept -> NH.Part -> OryHydraRequest req contentType res accept
_addMultiFormPart :: forall req contentType res accept.
OryHydraRequest req contentType res accept
-> Part -> OryHydraRequest req contentType res accept
_addMultiFormPart OryHydraRequest req contentType res accept
req Part
newpart =
let parts :: [Part]
parts = case Params -> ParamBody
paramsBody (forall req contentType res accept.
OryHydraRequest req contentType res accept -> Params
rParams OryHydraRequest req contentType res accept
req) of
ParamBodyMultipartFormData [Part]
_parts -> [Part]
_parts
ParamBody
_ -> []
in OryHydraRequest req contentType res accept
req forall a b. a -> (a -> b) -> b
& forall s t a b. ASetter s t a b -> b -> s -> t
L.set (forall req contentType res accept.
Lens_' (OryHydraRequest req contentType res accept) Params
rParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens_' Params ParamBody
paramsBodyL) ([Part] -> ParamBody
ParamBodyMultipartFormData (Part
newpart forall a. a -> [a] -> [a]
: [Part]
parts))
_setBodyBS :: OryHydraRequest req contentType res accept -> B.ByteString -> OryHydraRequest req contentType res accept
_setBodyBS :: forall req contentType res accept.
OryHydraRequest req contentType res accept
-> ByteString -> OryHydraRequest req contentType res accept
_setBodyBS OryHydraRequest req contentType res accept
req ByteString
body =
OryHydraRequest req contentType res accept
req forall a b. a -> (a -> b) -> b
& forall s t a b. ASetter s t a b -> b -> s -> t
L.set (forall req contentType res accept.
Lens_' (OryHydraRequest req contentType res accept) Params
rParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens_' Params ParamBody
paramsBodyL) (ByteString -> ParamBody
ParamBodyB ByteString
body)
_setBodyLBS :: OryHydraRequest req contentType res accept -> BL.ByteString -> OryHydraRequest req contentType res accept
_setBodyLBS :: forall req contentType res accept.
OryHydraRequest req contentType res accept
-> ByteString -> OryHydraRequest req contentType res accept
_setBodyLBS OryHydraRequest req contentType res accept
req ByteString
body =
OryHydraRequest req contentType res accept
req forall a b. a -> (a -> b) -> b
& forall s t a b. ASetter s t a b -> b -> s -> t
L.set (forall req contentType res accept.
Lens_' (OryHydraRequest req contentType res accept) Params
rParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens_' Params ParamBody
paramsBodyL) (ByteString -> ParamBody
ParamBodyBL ByteString
body)
_hasAuthType :: AuthMethod authMethod => OryHydraRequest req contentType res accept -> P.Proxy authMethod -> OryHydraRequest req contentType res accept
_hasAuthType :: forall authMethod req contentType res accept.
AuthMethod authMethod =>
OryHydraRequest req contentType res accept
-> Proxy authMethod -> OryHydraRequest req contentType res accept
_hasAuthType OryHydraRequest req contentType res accept
req Proxy authMethod
proxy =
OryHydraRequest req contentType res accept
req forall a b. a -> (a -> b) -> b
& forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
L.over forall req contentType res accept.
Lens_' (OryHydraRequest req contentType res accept) [TypeRep]
rAuthTypesL (forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
P.typeRep Proxy authMethod
proxy forall a. a -> [a] -> [a]
:)
toPath
:: WH.ToHttpApiData a
=> a -> BCL.ByteString
toPath :: forall a. ToHttpApiData a => a -> ByteString
toPath = Builder -> ByteString
BB.toLazyByteString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToHttpApiData a => a -> Builder
WH.toEncodedUrlPiece
toHeader :: WH.ToHttpApiData a => (NH.HeaderName, a) -> [NH.Header]
(HeaderName, a)
x = [forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. ToHttpApiData a => a -> ByteString
WH.toHeader (HeaderName, a)
x]
toForm :: WH.ToHttpApiData v => (BC.ByteString, v) -> WH.Form
toForm :: forall v. ToHttpApiData v => (ByteString, v) -> Form
toForm (ByteString
k,v
v) = forall a. ToForm a => a -> Form
WH.toForm [(ByteString -> String
BC.unpack ByteString
k,v
v)]
toQuery :: WH.ToHttpApiData a => (BC.ByteString, Maybe a) -> [NH.QueryItem]
toQuery :: forall a. ToHttpApiData a => (ByteString, Maybe a) -> Query
toQuery (ByteString, Maybe a)
x = [(forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) a -> ByteString
toQueryParam (ByteString, Maybe a)
x]
where toQueryParam :: a -> ByteString
toQueryParam = Text -> ByteString
T.encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToHttpApiData a => a -> Text
WH.toQueryParam
toPartialEscapeQuery :: B.ByteString -> NH.Query -> NH.PartialEscapeQuery
toPartialEscapeQuery :: ByteString -> Query -> PartialEscapeQuery
toPartialEscapeQuery ByteString
extraUnreserved Query
query = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(ByteString
k, Maybe ByteString
v) -> (ByteString
k, forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] ByteString -> [EscapeItem]
go Maybe ByteString
v)) Query
query
where go :: B.ByteString -> [NH.EscapeItem]
go :: ByteString -> [EscapeItem]
go ByteString
v = ByteString
v forall a b. a -> (a -> b) -> b
& (Word8 -> Word8 -> Bool) -> ByteString -> [ByteString]
B.groupBy (\Word8
a Word8
b -> Word8
a Word8 -> ByteString -> Bool
`B.notElem` ByteString
extraUnreserved Bool -> Bool -> Bool
&& Word8
b Word8 -> ByteString -> Bool
`B.notElem` ByteString
extraUnreserved)
forall a b. a -> (a -> b) -> b
& forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ByteString
xs -> if ByteString -> Bool
B.null ByteString
xs then ByteString -> EscapeItem
NH.QN ByteString
xs
else if HasCallStack => ByteString -> Word8
B.head ByteString
xs Word8 -> ByteString -> Bool
`B.elem` ByteString
extraUnreserved
then ByteString -> EscapeItem
NH.QN ByteString
xs
else ByteString -> EscapeItem
NH.QE ByteString
xs
)
data CollectionFormat
= CommaSeparated
| SpaceSeparated
| TabSeparated
| PipeSeparated
| MultiParamArray
toHeaderColl :: WH.ToHttpApiData a => CollectionFormat -> (NH.HeaderName, [a]) -> [NH.Header]
CollectionFormat
c (HeaderName, [a])
xs = forall (f :: * -> *) a b.
Traversable f =>
CollectionFormat
-> (f a -> [(b, ByteString)]) -> f [a] -> [(b, ByteString)]
_toColl CollectionFormat
c forall a. ToHttpApiData a => (HeaderName, a) -> RequestHeaders
toHeader (HeaderName, [a])
xs
toFormColl :: WH.ToHttpApiData v => CollectionFormat -> (BC.ByteString, [v]) -> WH.Form
toFormColl :: forall v.
ToHttpApiData v =>
CollectionFormat -> (ByteString, [v]) -> Form
toFormColl CollectionFormat
c (ByteString, [v])
xs = forall a. ToForm a => a -> Form
WH.toForm forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (HeaderName, ByteString) -> (String, String)
unpack forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b.
Traversable f =>
CollectionFormat
-> (f a -> [(b, ByteString)]) -> f [a] -> [(b, ByteString)]
_toColl CollectionFormat
c forall a. ToHttpApiData a => (HeaderName, a) -> RequestHeaders
toHeader forall a b. (a -> b) -> a -> b
$ forall {s} {b}. FoldCase s => (s, b) -> (CI s, b)
pack (ByteString, [v])
xs
where
pack :: (s, b) -> (CI s, b)
pack (s
k,b
v) = (forall s. FoldCase s => s -> CI s
CI.mk s
k, b
v)
unpack :: (HeaderName, ByteString) -> (String, String)
unpack (HeaderName
k,ByteString
v) = (ByteString -> String
BC.unpack (forall s. CI s -> s
CI.original HeaderName
k), ByteString -> String
BC.unpack ByteString
v)
toQueryColl :: WH.ToHttpApiData a => CollectionFormat -> (BC.ByteString, Maybe [a]) -> NH.Query
toQueryColl :: forall a.
ToHttpApiData a =>
CollectionFormat -> (ByteString, Maybe [a]) -> Query
toQueryColl CollectionFormat
c (ByteString, Maybe [a])
xs = forall (f :: * -> *) (t :: * -> *) a b.
(Traversable f, Traversable t, Alternative t) =>
CollectionFormat
-> (f (t a) -> [(b, t ByteString)])
-> f (t [a])
-> [(b, t ByteString)]
_toCollA CollectionFormat
c forall a. ToHttpApiData a => (ByteString, Maybe a) -> Query
toQuery (ByteString, Maybe [a])
xs
_toColl :: P.Traversable f => CollectionFormat -> (f a -> [(b, BC.ByteString)]) -> f [a] -> [(b, BC.ByteString)]
_toColl :: forall (f :: * -> *) a b.
Traversable f =>
CollectionFormat
-> (f a -> [(b, ByteString)]) -> f [a] -> [(b, ByteString)]
_toColl CollectionFormat
c f a -> [(b, ByteString)]
encode f [a]
xs = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. HasCallStack => Maybe a -> a
P.fromJust) (forall c (f :: * -> *) (t :: * -> *) a b.
(Monoid c, Traversable f, Traversable t, Alternative t) =>
CollectionFormat
-> (f (t a) -> [(b, t c)])
-> (Char -> c)
-> f (t [a])
-> [(b, t c)]
_toCollA' CollectionFormat
c f (Maybe a) -> [(b, Maybe ByteString)]
fencode Char -> ByteString
BC.singleton (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Maybe a
Just f [a]
xs))
where fencode :: f (Maybe a) -> [(b, Maybe ByteString)]
fencode = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Maybe a
Just) forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> [(b, ByteString)]
encode forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. HasCallStack => Maybe a -> a
P.fromJust
{-# INLINE fencode #-}
_toCollA :: (P.Traversable f, P.Traversable t, P.Alternative t) => CollectionFormat -> (f (t a) -> [(b, t BC.ByteString)]) -> f (t [a]) -> [(b, t BC.ByteString)]
_toCollA :: forall (f :: * -> *) (t :: * -> *) a b.
(Traversable f, Traversable t, Alternative t) =>
CollectionFormat
-> (f (t a) -> [(b, t ByteString)])
-> f (t [a])
-> [(b, t ByteString)]
_toCollA CollectionFormat
c f (t a) -> [(b, t ByteString)]
encode f (t [a])
xs = forall c (f :: * -> *) (t :: * -> *) a b.
(Monoid c, Traversable f, Traversable t, Alternative t) =>
CollectionFormat
-> (f (t a) -> [(b, t c)])
-> (Char -> c)
-> f (t [a])
-> [(b, t c)]
_toCollA' CollectionFormat
c f (t a) -> [(b, t ByteString)]
encode Char -> ByteString
BC.singleton f (t [a])
xs
_toCollA' :: (P.Monoid c, P.Traversable f, P.Traversable t, P.Alternative t) => CollectionFormat -> (f (t a) -> [(b, t c)]) -> (Char -> c) -> f (t [a]) -> [(b, t c)]
_toCollA' :: forall c (f :: * -> *) (t :: * -> *) a b.
(Monoid c, Traversable f, Traversable t, Alternative t) =>
CollectionFormat
-> (f (t a) -> [(b, t c)])
-> (Char -> c)
-> f (t [a])
-> [(b, t c)]
_toCollA' CollectionFormat
c f (t a) -> [(b, t c)]
encode Char -> c
one f (t [a])
xs = case CollectionFormat
c of
CollectionFormat
CommaSeparated -> c -> [(b, t c)]
go (Char -> c
one Char
',')
CollectionFormat
SpaceSeparated -> c -> [(b, t c)]
go (Char -> c
one Char
' ')
CollectionFormat
TabSeparated -> c -> [(b, t c)]
go (Char -> c
one Char
'\t')
CollectionFormat
PipeSeparated -> c -> [(b, t c)]
go (Char -> c
one Char
'|')
CollectionFormat
MultiParamArray -> [(b, t c)]
expandList
where
go :: c -> [(b, t c)]
go c
sep =
[forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
P.foldl1 (\(b
sk, t c
sv) (b
_, t c
v) -> (b
sk, (forall {a}. Semigroup a => a -> a -> a -> a
combine c
sep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> t c
sv forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> t c
v) forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> t c
sv forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> t c
v)) [(b, t c)]
expandList]
combine :: a -> a -> a -> a
combine a
sep a
x a
y = a
x forall a. Semigroup a => a -> a -> a
<> a
sep forall a. Semigroup a => a -> a -> a
<> a
y
expandList :: [(b, t c)]
expandList = (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
P.concatMap f (t a) -> [(b, t c)]
encode forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
P.traverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
P.traverse) forall (t :: * -> *) a. Foldable t => t a -> [a]
P.toList) f (t [a])
xs
{-# INLINE go #-}
{-# INLINE expandList #-}
{-# INLINE combine #-}
class P.Typeable a =>
AuthMethod a where
applyAuthMethod
:: OryHydraConfig
-> a
-> OryHydraRequest req contentType res accept
-> IO (OryHydraRequest req contentType res accept)
data AnyAuthMethod = forall a. AuthMethod a => AnyAuthMethod a deriving (P.Typeable)
instance AuthMethod AnyAuthMethod where applyAuthMethod :: forall req contentType res accept.
OryHydraConfig
-> AnyAuthMethod
-> OryHydraRequest req contentType res accept
-> IO (OryHydraRequest req contentType res accept)
applyAuthMethod OryHydraConfig
config (AnyAuthMethod a
a) OryHydraRequest req contentType res accept
req = forall a req contentType res accept.
AuthMethod a =>
OryHydraConfig
-> a
-> OryHydraRequest req contentType res accept
-> IO (OryHydraRequest req contentType res accept)
applyAuthMethod OryHydraConfig
config a
a OryHydraRequest req contentType res accept
req
data AuthMethodException = AuthMethodException String deriving (Int -> AuthMethodException -> ShowS
[AuthMethodException] -> ShowS
AuthMethodException -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AuthMethodException] -> ShowS
$cshowList :: [AuthMethodException] -> ShowS
show :: AuthMethodException -> String
$cshow :: AuthMethodException -> String
showsPrec :: Int -> AuthMethodException -> ShowS
$cshowsPrec :: Int -> AuthMethodException -> ShowS
P.Show, P.Typeable)
instance E.Exception AuthMethodException
_applyAuthMethods
:: OryHydraRequest req contentType res accept
-> OryHydraConfig
-> IO (OryHydraRequest req contentType res accept)
_applyAuthMethods :: forall req contentType res accept.
OryHydraRequest req contentType res accept
-> OryHydraConfig
-> IO (OryHydraRequest req contentType res accept)
_applyAuthMethods OryHydraRequest req contentType res accept
req config :: OryHydraConfig
config@(OryHydraConfig {configAuthMethods :: OryHydraConfig -> [AnyAuthMethod]
configAuthMethods = [AnyAuthMethod]
as}) =
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldlM OryHydraRequest req contentType res accept
-> AnyAuthMethod -> IO (OryHydraRequest req contentType res accept)
go OryHydraRequest req contentType res accept
req [AnyAuthMethod]
as
where
go :: OryHydraRequest req contentType res accept
-> AnyAuthMethod -> IO (OryHydraRequest req contentType res accept)
go OryHydraRequest req contentType res accept
r (AnyAuthMethod a
a) = forall a req contentType res accept.
AuthMethod a =>
OryHydraConfig
-> a
-> OryHydraRequest req contentType res accept
-> IO (OryHydraRequest req contentType res accept)
applyAuthMethod OryHydraConfig
config a
a OryHydraRequest req contentType res accept
r
#if MIN_VERSION_aeson(2,0,0)
_omitNulls :: [(A.Key, A.Value)] -> A.Value
#else
_omitNulls :: [(Text, A.Value)] -> A.Value
#endif
_omitNulls :: [(Key, Value)] -> Value
_omitNulls = [(Key, Value)] -> Value
A.object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
P.filter forall {a}. (a, Value) -> Bool
notNull
where
notNull :: (a, Value) -> Bool
notNull (a
_, Value
A.Null) = Bool
False
notNull (a, Value)
_ = Bool
True
_toFormItem :: (WH.ToHttpApiData a, Functor f) => t -> f a -> f (t, [Text])
_toFormItem :: forall a (f :: * -> *) t.
(ToHttpApiData a, Functor f) =>
t -> f a -> f (t, [Text])
_toFormItem t
name f a
x = (t
name,) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. a -> [a] -> [a]
:[]) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToHttpApiData a => a -> Text
WH.toQueryParam forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f a
x
_emptyToNothing :: Maybe String -> Maybe String
_emptyToNothing :: Maybe String -> Maybe String
_emptyToNothing (Just String
"") = forall a. Maybe a
Nothing
_emptyToNothing Maybe String
x = Maybe String
x
{-# INLINE _emptyToNothing #-}
_memptyToNothing :: (P.Monoid a, P.Eq a) => Maybe a -> Maybe a
_memptyToNothing :: forall a. (Monoid a, Eq a) => Maybe a -> Maybe a
_memptyToNothing (Just a
x) | a
x forall a. Eq a => a -> a -> Bool
P.== forall a. Monoid a => a
P.mempty = forall a. Maybe a
Nothing
_memptyToNothing Maybe a
x = Maybe a
x
{-# INLINE _memptyToNothing #-}
newtype DateTime = DateTime { DateTime -> UTCTime
unDateTime :: TI.UTCTime }
deriving (DateTime -> DateTime -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DateTime -> DateTime -> Bool
$c/= :: DateTime -> DateTime -> Bool
== :: DateTime -> DateTime -> Bool
$c== :: DateTime -> DateTime -> Bool
P.Eq,Typeable DateTime
DateTime -> DataType
DateTime -> Constr
(forall b. Data b => b -> b) -> DateTime -> DateTime
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) -> DateTime -> u
forall u. (forall d. Data d => d -> u) -> DateTime -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DateTime -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DateTime -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DateTime
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DateTime -> c DateTime
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DateTime)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DateTime)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DateTime -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DateTime -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> DateTime -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> DateTime -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DateTime -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DateTime -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DateTime -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DateTime -> r
gmapT :: (forall b. Data b => b -> b) -> DateTime -> DateTime
$cgmapT :: (forall b. Data b => b -> b) -> DateTime -> DateTime
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DateTime)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DateTime)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DateTime)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DateTime)
dataTypeOf :: DateTime -> DataType
$cdataTypeOf :: DateTime -> DataType
toConstr :: DateTime -> Constr
$ctoConstr :: DateTime -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DateTime
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DateTime
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DateTime -> c DateTime
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DateTime -> c DateTime
P.Data,Eq DateTime
DateTime -> DateTime -> Bool
DateTime -> DateTime -> Ordering
DateTime -> DateTime -> DateTime
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 :: DateTime -> DateTime -> DateTime
$cmin :: DateTime -> DateTime -> DateTime
max :: DateTime -> DateTime -> DateTime
$cmax :: DateTime -> DateTime -> DateTime
>= :: DateTime -> DateTime -> Bool
$c>= :: DateTime -> DateTime -> Bool
> :: DateTime -> DateTime -> Bool
$c> :: DateTime -> DateTime -> Bool
<= :: DateTime -> DateTime -> Bool
$c<= :: DateTime -> DateTime -> Bool
< :: DateTime -> DateTime -> Bool
$c< :: DateTime -> DateTime -> Bool
compare :: DateTime -> DateTime -> Ordering
$ccompare :: DateTime -> DateTime -> Ordering
P.Ord,P.Typeable,DateTime -> ()
forall a. (a -> ()) -> NFData a
rnf :: DateTime -> ()
$crnf :: DateTime -> ()
NF.NFData)
instance A.FromJSON DateTime where
parseJSON :: Value -> Parser DateTime
parseJSON = forall a. String -> (Text -> Parser a) -> Value -> Parser a
A.withText String
"DateTime" (forall (m :: * -> *).
(MonadFail m, Alternative m) =>
String -> m DateTime
_readDateTime forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack)
instance A.ToJSON DateTime where
toJSON :: DateTime -> Value
toJSON (DateTime UTCTime
t) = forall a. ToJSON a => a -> Value
A.toJSON (forall t. (t ~ UTCTime, FormatTime t) => t -> String
_showDateTime UTCTime
t)
instance WH.FromHttpApiData DateTime where
parseUrlPiece :: Text -> Either Text DateTime
parseUrlPiece = forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (forall a b. a -> Either a b
P.Left Text
"parseUrlPiece @DateTime") forall a b. b -> Either a b
P.Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *).
(MonadFail m, Alternative m) =>
String -> m DateTime
_readDateTime forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
instance WH.ToHttpApiData DateTime where
toUrlPiece :: DateTime -> Text
toUrlPiece (DateTime UTCTime
t) = String -> Text
T.pack (forall t. (t ~ UTCTime, FormatTime t) => t -> String
_showDateTime UTCTime
t)
instance P.Show DateTime where
show :: DateTime -> String
show (DateTime UTCTime
t) = forall t. (t ~ UTCTime, FormatTime t) => t -> String
_showDateTime UTCTime
t
instance MimeRender MimeMultipartFormData DateTime where
mimeRender :: Proxy MimeMultipartFormData -> DateTime -> ByteString
mimeRender Proxy MimeMultipartFormData
_ = forall a. ToHttpApiData a => a -> ByteString
mimeRenderDefaultMultipartFormData
_readDateTime :: (MonadFail m, Alternative m) => String -> m DateTime
_readDateTime :: forall (m :: * -> *).
(MonadFail m, Alternative m) =>
String -> m DateTime
_readDateTime String
s =
UTCTime -> DateTime
DateTime forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t (m :: * -> *).
(ParseTime t, MonadFail m, Alternative m) =>
String -> m t
_parseISO8601 String
s
{-# INLINE _readDateTime #-}
_showDateTime :: (t ~ TI.UTCTime, TI.FormatTime t) => t -> String
_showDateTime :: forall t. (t ~ UTCTime, FormatTime t) => t -> String
_showDateTime =
UTCTime -> String
TI.formatISO8601Millis
{-# INLINE _showDateTime #-}
_parseISO8601 :: (TI.ParseTime t, MonadFail m, Alternative m) => String -> m t
_parseISO8601 :: forall t (m :: * -> *).
(ParseTime t, MonadFail m, Alternative m) =>
String -> m t
_parseISO8601 String
t =
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
P.asum forall a b. (a -> b) -> a -> b
$
forall a b c. (a -> b -> c) -> b -> a -> c
P.flip (forall (m :: * -> *) t.
(MonadFail m, ParseTime t) =>
Bool -> TimeLocale -> String -> String -> m t
TI.parseTimeM Bool
True TimeLocale
TI.defaultTimeLocale) String
t forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
[String
"%FT%T%QZ", String
"%FT%T%Q%z", String
"%FT%T%Q%Z"]
{-# INLINE _parseISO8601 #-}
newtype Date = Date { Date -> Day
unDate :: TI.Day }
deriving (Int -> Date
Date -> Int
Date -> [Date]
Date -> Date
Date -> Date -> [Date]
Date -> Date -> Date -> [Date]
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 :: Date -> Date -> Date -> [Date]
$cenumFromThenTo :: Date -> Date -> Date -> [Date]
enumFromTo :: Date -> Date -> [Date]
$cenumFromTo :: Date -> Date -> [Date]
enumFromThen :: Date -> Date -> [Date]
$cenumFromThen :: Date -> Date -> [Date]
enumFrom :: Date -> [Date]
$cenumFrom :: Date -> [Date]
fromEnum :: Date -> Int
$cfromEnum :: Date -> Int
toEnum :: Int -> Date
$ctoEnum :: Int -> Date
pred :: Date -> Date
$cpred :: Date -> Date
succ :: Date -> Date
$csucc :: Date -> Date
P.Enum,Date -> Date -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Date -> Date -> Bool
$c/= :: Date -> Date -> Bool
== :: Date -> Date -> Bool
$c== :: Date -> Date -> Bool
P.Eq,Typeable Date
Date -> DataType
Date -> Constr
(forall b. Data b => b -> b) -> Date -> Date
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) -> Date -> u
forall u. (forall d. Data d => d -> u) -> Date -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Date -> m Date
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Date -> m Date
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Date
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Date -> c Date
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Date)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Date)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Date -> m Date
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Date -> m Date
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Date -> m Date
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Date -> m Date
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Date -> m Date
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Date -> m Date
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Date -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Date -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Date -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Date -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r
gmapT :: (forall b. Data b => b -> b) -> Date -> Date
$cgmapT :: (forall b. Data b => b -> b) -> Date -> Date
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Date)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Date)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Date)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Date)
dataTypeOf :: Date -> DataType
$cdataTypeOf :: Date -> DataType
toConstr :: Date -> Constr
$ctoConstr :: Date -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Date
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Date
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Date -> c Date
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Date -> c Date
P.Data,Eq Date
Date -> Date -> Bool
Date -> Date -> Ordering
Date -> Date -> Date
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 :: Date -> Date -> Date
$cmin :: Date -> Date -> Date
max :: Date -> Date -> Date
$cmax :: Date -> Date -> Date
>= :: Date -> Date -> Bool
$c>= :: Date -> Date -> Bool
> :: Date -> Date -> Bool
$c> :: Date -> Date -> Bool
<= :: Date -> Date -> Bool
$c<= :: Date -> Date -> Bool
< :: Date -> Date -> Bool
$c< :: Date -> Date -> Bool
compare :: Date -> Date -> Ordering
$ccompare :: Date -> Date -> Ordering
P.Ord,Ord Date
(Date, Date) -> Int
(Date, Date) -> [Date]
(Date, Date) -> Date -> Bool
(Date, Date) -> Date -> Int
forall a.
Ord a
-> ((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
unsafeRangeSize :: (Date, Date) -> Int
$cunsafeRangeSize :: (Date, Date) -> Int
rangeSize :: (Date, Date) -> Int
$crangeSize :: (Date, Date) -> Int
inRange :: (Date, Date) -> Date -> Bool
$cinRange :: (Date, Date) -> Date -> Bool
unsafeIndex :: (Date, Date) -> Date -> Int
$cunsafeIndex :: (Date, Date) -> Date -> Int
index :: (Date, Date) -> Date -> Int
$cindex :: (Date, Date) -> Date -> Int
range :: (Date, Date) -> [Date]
$crange :: (Date, Date) -> [Date]
P.Ix,Date -> ()
forall a. (a -> ()) -> NFData a
rnf :: Date -> ()
$crnf :: Date -> ()
NF.NFData)
instance A.FromJSON Date where
parseJSON :: Value -> Parser Date
parseJSON = forall a. String -> (Text -> Parser a) -> Value -> Parser a
A.withText String
"Date" (forall (m :: * -> *). MonadFail m => String -> m Date
_readDate forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack)
instance A.ToJSON Date where
toJSON :: Date -> Value
toJSON (Date Day
t) = forall a. ToJSON a => a -> Value
A.toJSON (forall t. FormatTime t => t -> String
_showDate Day
t)
instance WH.FromHttpApiData Date where
parseUrlPiece :: Text -> Either Text Date
parseUrlPiece = forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (forall a b. a -> Either a b
P.Left Text
"parseUrlPiece @Date") forall a b. b -> Either a b
P.Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). MonadFail m => String -> m Date
_readDate forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
instance WH.ToHttpApiData Date where
toUrlPiece :: Date -> Text
toUrlPiece (Date Day
t) = String -> Text
T.pack (forall t. FormatTime t => t -> String
_showDate Day
t)
instance P.Show Date where
show :: Date -> String
show (Date Day
t) = forall t. FormatTime t => t -> String
_showDate Day
t
instance MimeRender MimeMultipartFormData Date where
mimeRender :: Proxy MimeMultipartFormData -> Date -> ByteString
mimeRender Proxy MimeMultipartFormData
_ = forall a. ToHttpApiData a => a -> ByteString
mimeRenderDefaultMultipartFormData
_readDate :: MonadFail m => String -> m Date
_readDate :: forall (m :: * -> *). MonadFail m => String -> m Date
_readDate String
s = Day -> Date
Date forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) t.
(MonadFail m, ParseTime t) =>
Bool -> TimeLocale -> String -> String -> m t
TI.parseTimeM Bool
True TimeLocale
TI.defaultTimeLocale String
"%Y-%m-%d" String
s
{-# INLINE _readDate #-}
_showDate :: TI.FormatTime t => t -> String
_showDate :: forall t. FormatTime t => t -> String
_showDate =
forall t. FormatTime t => TimeLocale -> String -> t -> String
TI.formatTime TimeLocale
TI.defaultTimeLocale String
"%Y-%m-%d"
{-# INLINE _showDate #-}
newtype ByteArray = ByteArray { ByteArray -> ByteString
unByteArray :: BL.ByteString }
deriving (ByteArray -> ByteArray -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ByteArray -> ByteArray -> Bool
$c/= :: ByteArray -> ByteArray -> Bool
== :: ByteArray -> ByteArray -> Bool
$c== :: ByteArray -> ByteArray -> Bool
P.Eq,Typeable ByteArray
ByteArray -> DataType
ByteArray -> Constr
(forall b. Data b => b -> b) -> ByteArray -> ByteArray
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) -> ByteArray -> u
forall u. (forall d. Data d => d -> u) -> ByteArray -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ByteArray -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ByteArray -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ByteArray
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ByteArray -> c ByteArray
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ByteArray)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteArray)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ByteArray -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ByteArray -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ByteArray -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ByteArray -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ByteArray -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ByteArray -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ByteArray -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ByteArray -> r
gmapT :: (forall b. Data b => b -> b) -> ByteArray -> ByteArray
$cgmapT :: (forall b. Data b => b -> b) -> ByteArray -> ByteArray
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteArray)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteArray)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ByteArray)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ByteArray)
dataTypeOf :: ByteArray -> DataType
$cdataTypeOf :: ByteArray -> DataType
toConstr :: ByteArray -> Constr
$ctoConstr :: ByteArray -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ByteArray
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ByteArray
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ByteArray -> c ByteArray
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ByteArray -> c ByteArray
P.Data,Eq ByteArray
ByteArray -> ByteArray -> Bool
ByteArray -> ByteArray -> Ordering
ByteArray -> ByteArray -> ByteArray
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 :: ByteArray -> ByteArray -> ByteArray
$cmin :: ByteArray -> ByteArray -> ByteArray
max :: ByteArray -> ByteArray -> ByteArray
$cmax :: ByteArray -> ByteArray -> ByteArray
>= :: ByteArray -> ByteArray -> Bool
$c>= :: ByteArray -> ByteArray -> Bool
> :: ByteArray -> ByteArray -> Bool
$c> :: ByteArray -> ByteArray -> Bool
<= :: ByteArray -> ByteArray -> Bool
$c<= :: ByteArray -> ByteArray -> Bool
< :: ByteArray -> ByteArray -> Bool
$c< :: ByteArray -> ByteArray -> Bool
compare :: ByteArray -> ByteArray -> Ordering
$ccompare :: ByteArray -> ByteArray -> Ordering
P.Ord,P.Typeable,ByteArray -> ()
forall a. (a -> ()) -> NFData a
rnf :: ByteArray -> ()
$crnf :: ByteArray -> ()
NF.NFData)
instance A.FromJSON ByteArray where
parseJSON :: Value -> Parser ByteArray
parseJSON = forall a. String -> (Text -> Parser a) -> Value -> Parser a
A.withText String
"ByteArray" forall (m :: * -> *). MonadFail m => Text -> m ByteArray
_readByteArray
instance A.ToJSON ByteArray where
toJSON :: ByteArray -> Value
toJSON = forall a. ToJSON a => a -> Value
A.toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteArray -> Text
_showByteArray
instance WH.FromHttpApiData ByteArray where
parseUrlPiece :: Text -> Either Text ByteArray
parseUrlPiece = forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (forall a b. a -> Either a b
P.Left Text
"parseUrlPiece @ByteArray") forall a b. b -> Either a b
P.Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). MonadFail m => Text -> m ByteArray
_readByteArray
instance WH.ToHttpApiData ByteArray where
toUrlPiece :: ByteArray -> Text
toUrlPiece = ByteArray -> Text
_showByteArray
instance P.Show ByteArray where
show :: ByteArray -> String
show = Text -> String
T.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteArray -> Text
_showByteArray
instance MimeRender MimeMultipartFormData ByteArray where
mimeRender :: Proxy MimeMultipartFormData -> ByteArray -> ByteString
mimeRender Proxy MimeMultipartFormData
_ = forall a. ToHttpApiData a => a -> ByteString
mimeRenderDefaultMultipartFormData
_readByteArray :: MonadFail m => Text -> m ByteArray
_readByteArray :: forall (m :: * -> *). MonadFail m => Text -> m ByteArray
_readByteArray = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
P.either forall (m :: * -> *) a. MonadFail m => String -> m a
P.fail (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteArray
ByteArray) forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String ByteString
BL64.decode forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL.fromStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
T.encodeUtf8
{-# INLINE _readByteArray #-}
_showByteArray :: ByteArray -> Text
_showByteArray :: ByteArray -> Text
_showByteArray = ByteString -> Text
T.decodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL64.encode forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteArray -> ByteString
unByteArray
{-# INLINE _showByteArray #-}
newtype Binary = Binary { Binary -> ByteString
unBinary :: BL.ByteString }
deriving (Binary -> Binary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Binary -> Binary -> Bool
$c/= :: Binary -> Binary -> Bool
== :: Binary -> Binary -> Bool
$c== :: Binary -> Binary -> Bool
P.Eq,Typeable Binary
Binary -> DataType
Binary -> Constr
(forall b. Data b => b -> b) -> Binary -> Binary
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) -> Binary -> u
forall u. (forall d. Data d => d -> u) -> Binary -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Binary -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Binary -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Binary
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binary -> c Binary
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Binary)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Binary)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Binary -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Binary -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Binary -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Binary -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Binary -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Binary -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Binary -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Binary -> r
gmapT :: (forall b. Data b => b -> b) -> Binary -> Binary
$cgmapT :: (forall b. Data b => b -> b) -> Binary -> Binary
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Binary)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Binary)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Binary)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Binary)
dataTypeOf :: Binary -> DataType
$cdataTypeOf :: Binary -> DataType
toConstr :: Binary -> Constr
$ctoConstr :: Binary -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Binary
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Binary
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binary -> c Binary
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binary -> c Binary
P.Data,Eq Binary
Binary -> Binary -> Bool
Binary -> Binary -> Ordering
Binary -> Binary -> Binary
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 :: Binary -> Binary -> Binary
$cmin :: Binary -> Binary -> Binary
max :: Binary -> Binary -> Binary
$cmax :: Binary -> Binary -> Binary
>= :: Binary -> Binary -> Bool
$c>= :: Binary -> Binary -> Bool
> :: Binary -> Binary -> Bool
$c> :: Binary -> Binary -> Bool
<= :: Binary -> Binary -> Bool
$c<= :: Binary -> Binary -> Bool
< :: Binary -> Binary -> Bool
$c< :: Binary -> Binary -> Bool
compare :: Binary -> Binary -> Ordering
$ccompare :: Binary -> Binary -> Ordering
P.Ord,P.Typeable,Binary -> ()
forall a. (a -> ()) -> NFData a
rnf :: Binary -> ()
$crnf :: Binary -> ()
NF.NFData)
instance A.FromJSON Binary where
parseJSON :: Value -> Parser Binary
parseJSON = forall a. String -> (Text -> Parser a) -> Value -> Parser a
A.withText String
"Binary" forall (m :: * -> *). MonadFail m => Text -> m Binary
_readBinaryBase64
instance A.ToJSON Binary where
toJSON :: Binary -> Value
toJSON = forall a. ToJSON a => a -> Value
A.toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. Binary -> Text
_showBinaryBase64
instance WH.FromHttpApiData Binary where
parseUrlPiece :: Text -> Either Text Binary
parseUrlPiece = forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (forall a b. a -> Either a b
P.Left Text
"parseUrlPiece @Binary") forall a b. b -> Either a b
P.Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). MonadFail m => Text -> m Binary
_readBinaryBase64
instance WH.ToHttpApiData Binary where
toUrlPiece :: Binary -> Text
toUrlPiece = Binary -> Text
_showBinaryBase64
instance P.Show Binary where
show :: Binary -> String
show = Text -> String
T.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. Binary -> Text
_showBinaryBase64
instance MimeRender MimeMultipartFormData Binary where
mimeRender :: Proxy MimeMultipartFormData -> Binary -> ByteString
mimeRender Proxy MimeMultipartFormData
_ = Binary -> ByteString
unBinary
_readBinaryBase64 :: MonadFail m => Text -> m Binary
_readBinaryBase64 :: forall (m :: * -> *). MonadFail m => Text -> m Binary
_readBinaryBase64 = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
P.either forall (m :: * -> *) a. MonadFail m => String -> m a
P.fail (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Binary
Binary) forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String ByteString
BL64.decode forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL.fromStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
T.encodeUtf8
{-# INLINE _readBinaryBase64 #-}
_showBinaryBase64 :: Binary -> Text
_showBinaryBase64 :: Binary -> Text
_showBinaryBase64 = ByteString -> Text
T.decodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL64.encode forall b c a. (b -> c) -> (a -> b) -> a -> c
. Binary -> ByteString
unBinary
{-# INLINE _showBinaryBase64 #-}
type Lens_' s a = Lens_ s s a a
type Lens_ s t a b = forall (f :: K.Type -> K.Type). Functor f => (a -> f b) -> s -> f t