{-
   Neptune Backend API

   No description provided (generated by Openapi Generator https://github.com/openapitools/openapi-generator)

   OpenAPI Version: 3.0.1
   Neptune Backend API API version: 2.8
   Generated by OpenAPI Generator (https://openapi-generator.tech)
-}

{-|
Module : Neptune.Backend.Core
-}

{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE ExistentialQuantification  #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE NamedFieldPuns             #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE RankNTypes                 #-}
{-# LANGUAGE RecordWildCards            #-}
{-# LANGUAGE ScopedTypeVariables        #-}
{-# LANGUAGE TupleSections              #-}
{-# LANGUAGE TypeFamilies               #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-unused-binds -fno-warn-unused-imports #-}

module Neptune.Backend.Core where

import           Neptune.Backend.Logging
import           Neptune.Backend.MimeTypes

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, TypeRep,
                                                             Typeable, typeRep)
import qualified Data.Foldable                         as P
import qualified Data.Ix                               as P
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                   (Alternative, (<|>))
import           Control.Monad.Fail                    (MonadFail)
import           Data.Foldable                         (foldlM)
import           Data.Function                         ((&))
import           Data.Monoid                           ((<>))
import           Data.Text                             (Text)
import           Prelude                               (Bool (..), Char,
                                                        Functor, IO, Maybe (..),
                                                        Monad, String, fmap,
                                                        mempty, pure, return,
                                                        show, ($), (.), (<$>),
                                                        (<*>))

-- * NeptuneBackendConfig

-- |
data NeptuneBackendConfig = NeptuneBackendConfig
  { NeptuneBackendConfig -> ByteString
configHost                :: BCL.ByteString -- ^ host supplied in the Request
  , NeptuneBackendConfig -> Text
configUserAgent           :: Text -- ^ user-agent supplied in the Request
  , NeptuneBackendConfig
-> forall (m :: * -> *). MonadIO m => LogContext -> LogExec m
configLogExecWithContext  :: LogExecWithContext -- ^ Run a block using a Logger instance
  , NeptuneBackendConfig -> LogContext
configLogContext          :: LogContext -- ^ Configures the logger
  , NeptuneBackendConfig -> [AnyAuthMethod]
configAuthMethods         :: [AnyAuthMethod] -- ^ List of configured auth methods
  , NeptuneBackendConfig -> Bool
configValidateAuthMethods :: Bool -- ^ throw exceptions if auth methods are not configured
  }

-- | display the config
instance P.Show NeptuneBackendConfig where
  show :: NeptuneBackendConfig -> String
show NeptuneBackendConfig
c =
    String -> String -> ShowS
forall r. PrintfType r => String -> r
T.printf
      String
"{ configHost = %v, configUserAgent = %v, ..}"
      (ByteString -> String
forall a. Show a => a -> String
show (NeptuneBackendConfig -> ByteString
configHost NeptuneBackendConfig
c))
      (Text -> String
forall a. Show a => a -> String
show (NeptuneBackendConfig -> Text
configUserAgent NeptuneBackendConfig
c))

-- | constructs a default NeptuneBackendConfig
--
-- configHost:
--
-- @http://localhost@
--
-- configUserAgent:
--
-- @"neptune-backend/0.1.0.0"@
--
newConfig :: IO NeptuneBackendConfig
newConfig :: IO NeptuneBackendConfig
newConfig = do
    LogContext
logCxt <- IO LogContext
initLogContext
    NeptuneBackendConfig -> IO NeptuneBackendConfig
forall (m :: * -> *) a. Monad m => a -> m a
return (NeptuneBackendConfig -> IO NeptuneBackendConfig)
-> NeptuneBackendConfig -> IO NeptuneBackendConfig
forall a b. (a -> b) -> a -> b
$ NeptuneBackendConfig :: ByteString
-> Text
-> (forall (m :: * -> *). MonadIO m => LogContext -> LogExec m)
-> LogContext
-> [AnyAuthMethod]
-> Bool
-> NeptuneBackendConfig
NeptuneBackendConfig
        { configHost :: ByteString
configHost = ByteString
"http://localhost"
        , configUserAgent :: Text
configUserAgent = Text
"neptune-backend/0.1.0.0"
        , configLogExecWithContext :: forall (m :: * -> *). MonadIO m => LogContext -> LogExec m
configLogExecWithContext = forall (m :: * -> *). MonadIO m => LogContext -> LogExec m
runDefaultLogExecWithContext
        , configLogContext :: LogContext
configLogContext = LogContext
logCxt
        , configAuthMethods :: [AnyAuthMethod]
configAuthMethods = []
        , configValidateAuthMethods :: Bool
configValidateAuthMethods = Bool
True
        }

-- | updates config use AuthMethod on matching requests
addAuthMethod :: AuthMethod auth => NeptuneBackendConfig -> auth -> NeptuneBackendConfig
addAuthMethod :: NeptuneBackendConfig -> auth -> NeptuneBackendConfig
addAuthMethod config :: NeptuneBackendConfig
config@NeptuneBackendConfig {configAuthMethods :: NeptuneBackendConfig -> [AnyAuthMethod]
configAuthMethods = [AnyAuthMethod]
as} auth
a =
  NeptuneBackendConfig
config { configAuthMethods :: [AnyAuthMethod]
configAuthMethods = auth -> AnyAuthMethod
forall a. AuthMethod a => a -> AnyAuthMethod
AnyAuthMethod auth
a AnyAuthMethod -> [AnyAuthMethod] -> [AnyAuthMethod]
forall a. a -> [a] -> [a]
: [AnyAuthMethod]
as}

-- | updates the config to use stdout logging
withStdoutLogging :: NeptuneBackendConfig -> IO NeptuneBackendConfig
withStdoutLogging :: NeptuneBackendConfig -> IO NeptuneBackendConfig
withStdoutLogging NeptuneBackendConfig
p = do
    LogContext
logCxt <- LogContext -> IO LogContext
stdoutLoggingContext (NeptuneBackendConfig -> LogContext
configLogContext NeptuneBackendConfig
p)
    NeptuneBackendConfig -> IO NeptuneBackendConfig
forall (m :: * -> *) a. Monad m => a -> m a
return (NeptuneBackendConfig -> IO NeptuneBackendConfig)
-> NeptuneBackendConfig -> IO NeptuneBackendConfig
forall a b. (a -> b) -> a -> b
$ NeptuneBackendConfig
p { configLogExecWithContext :: forall (m :: * -> *). MonadIO m => LogContext -> LogExec m
configLogExecWithContext = forall (m :: * -> *). MonadIO m => LogContext -> LogExec m
stdoutLoggingExec, configLogContext :: LogContext
configLogContext = LogContext
logCxt }

-- | updates the config to use stderr logging
withStderrLogging :: NeptuneBackendConfig -> IO NeptuneBackendConfig
withStderrLogging :: NeptuneBackendConfig -> IO NeptuneBackendConfig
withStderrLogging NeptuneBackendConfig
p = do
    LogContext
logCxt <- LogContext -> IO LogContext
stderrLoggingContext (NeptuneBackendConfig -> LogContext
configLogContext NeptuneBackendConfig
p)
    NeptuneBackendConfig -> IO NeptuneBackendConfig
forall (m :: * -> *) a. Monad m => a -> m a
return (NeptuneBackendConfig -> IO NeptuneBackendConfig)
-> NeptuneBackendConfig -> IO NeptuneBackendConfig
forall a b. (a -> b) -> a -> b
$ NeptuneBackendConfig
p { configLogExecWithContext :: forall (m :: * -> *). MonadIO m => LogContext -> LogExec m
configLogExecWithContext = forall (m :: * -> *). MonadIO m => LogContext -> LogExec m
stderrLoggingExec, configLogContext :: LogContext
configLogContext = LogContext
logCxt }

-- | updates the config to disable logging
withNoLogging :: NeptuneBackendConfig -> NeptuneBackendConfig
withNoLogging :: NeptuneBackendConfig -> NeptuneBackendConfig
withNoLogging NeptuneBackendConfig
p = NeptuneBackendConfig
p { configLogExecWithContext :: forall (m :: * -> *). MonadIO m => LogContext -> LogExec m
configLogExecWithContext =  forall (m :: * -> *). MonadIO m => LogContext -> LogExec m
runNullLogExec}

-- * NeptuneBackendRequest

-- | Represents a request.
--
--   Type Variables:
--
--   * req - request operation
--   * contentType - 'MimeType' associated with request body
--   * res - response model
--   * accept - 'MimeType' associated with response body
data NeptuneBackendRequest req contentType res accept = NeptuneBackendRequest
  { NeptuneBackendRequest req contentType res accept -> Method
rMethod    :: NH.Method   -- ^ Method of NeptuneBackendRequest
  , NeptuneBackendRequest req contentType res accept -> [ByteString]
rUrlPath   :: [BCL.ByteString] -- ^ Endpoint of NeptuneBackendRequest
  , NeptuneBackendRequest req contentType res accept -> Params
rParams    :: Params -- ^ params of NeptuneBackendRequest
  , NeptuneBackendRequest req contentType res accept -> [TypeRep]
rAuthTypes :: [P.TypeRep] -- ^ types of auth methods
  }
  deriving (Int -> NeptuneBackendRequest req contentType res accept -> ShowS
[NeptuneBackendRequest req contentType res accept] -> ShowS
NeptuneBackendRequest req contentType res accept -> String
(Int -> NeptuneBackendRequest req contentType res accept -> ShowS)
-> (NeptuneBackendRequest req contentType res accept -> String)
-> ([NeptuneBackendRequest req contentType res accept] -> ShowS)
-> Show (NeptuneBackendRequest req contentType res accept)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall req contentType res accept.
Int -> NeptuneBackendRequest req contentType res accept -> ShowS
forall req contentType res accept.
[NeptuneBackendRequest req contentType res accept] -> ShowS
forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> String
showList :: [NeptuneBackendRequest req contentType res accept] -> ShowS
$cshowList :: forall req contentType res accept.
[NeptuneBackendRequest req contentType res accept] -> ShowS
show :: NeptuneBackendRequest req contentType res accept -> String
$cshow :: forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> String
showsPrec :: Int -> NeptuneBackendRequest req contentType res accept -> ShowS
$cshowsPrec :: forall req contentType res accept.
Int -> NeptuneBackendRequest req contentType res accept -> ShowS
P.Show)

-- | 'rMethod' Lens
rMethodL :: Lens_' (NeptuneBackendRequest req contentType res accept) NH.Method
rMethodL :: (Method -> f Method)
-> NeptuneBackendRequest req contentType res accept
-> f (NeptuneBackendRequest req contentType res accept)
rMethodL Method -> f Method
f NeptuneBackendRequest{[TypeRep]
[ByteString]
Method
Params
rAuthTypes :: [TypeRep]
rParams :: Params
rUrlPath :: [ByteString]
rMethod :: Method
rAuthTypes :: forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> [TypeRep]
rParams :: forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> Params
rUrlPath :: forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> [ByteString]
rMethod :: forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> Method
..} = (\Method
rMethod -> NeptuneBackendRequest :: forall req contentType res accept.
Method
-> [ByteString]
-> Params
-> [TypeRep]
-> NeptuneBackendRequest req contentType res accept
NeptuneBackendRequest { Method
rMethod :: Method
rMethod :: Method
rMethod, [TypeRep]
[ByteString]
Params
rAuthTypes :: [TypeRep]
rParams :: Params
rUrlPath :: [ByteString]
rAuthTypes :: [TypeRep]
rParams :: Params
rUrlPath :: [ByteString]
..} ) (Method -> NeptuneBackendRequest req contentType res accept)
-> f Method -> f (NeptuneBackendRequest req contentType res accept)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Method -> f Method
f Method
rMethod
{-# INLINE rMethodL #-}

-- | 'rUrlPath' Lens
rUrlPathL :: Lens_' (NeptuneBackendRequest req contentType res accept) [BCL.ByteString]
rUrlPathL :: ([ByteString] -> f [ByteString])
-> NeptuneBackendRequest req contentType res accept
-> f (NeptuneBackendRequest req contentType res accept)
rUrlPathL [ByteString] -> f [ByteString]
f NeptuneBackendRequest{[TypeRep]
[ByteString]
Method
Params
rAuthTypes :: [TypeRep]
rParams :: Params
rUrlPath :: [ByteString]
rMethod :: Method
rAuthTypes :: forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> [TypeRep]
rParams :: forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> Params
rUrlPath :: forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> [ByteString]
rMethod :: forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> Method
..} = (\[ByteString]
rUrlPath -> NeptuneBackendRequest :: forall req contentType res accept.
Method
-> [ByteString]
-> Params
-> [TypeRep]
-> NeptuneBackendRequest req contentType res accept
NeptuneBackendRequest { [ByteString]
rUrlPath :: [ByteString]
rUrlPath :: [ByteString]
rUrlPath, [TypeRep]
Method
Params
rAuthTypes :: [TypeRep]
rParams :: Params
rMethod :: Method
rAuthTypes :: [TypeRep]
rParams :: Params
rMethod :: Method
..} ) ([ByteString] -> NeptuneBackendRequest req contentType res accept)
-> f [ByteString]
-> f (NeptuneBackendRequest req contentType res accept)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ByteString] -> f [ByteString]
f [ByteString]
rUrlPath
{-# INLINE rUrlPathL #-}

-- | 'rParams' Lens
rParamsL :: Lens_' (NeptuneBackendRequest req contentType res accept) Params
rParamsL :: (Params -> f Params)
-> NeptuneBackendRequest req contentType res accept
-> f (NeptuneBackendRequest req contentType res accept)
rParamsL Params -> f Params
f NeptuneBackendRequest{[TypeRep]
[ByteString]
Method
Params
rAuthTypes :: [TypeRep]
rParams :: Params
rUrlPath :: [ByteString]
rMethod :: Method
rAuthTypes :: forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> [TypeRep]
rParams :: forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> Params
rUrlPath :: forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> [ByteString]
rMethod :: forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> Method
..} = (\Params
rParams -> NeptuneBackendRequest :: forall req contentType res accept.
Method
-> [ByteString]
-> Params
-> [TypeRep]
-> NeptuneBackendRequest req contentType res accept
NeptuneBackendRequest { Params
rParams :: Params
rParams :: Params
rParams, [TypeRep]
[ByteString]
Method
rAuthTypes :: [TypeRep]
rUrlPath :: [ByteString]
rMethod :: Method
rAuthTypes :: [TypeRep]
rUrlPath :: [ByteString]
rMethod :: Method
..} ) (Params -> NeptuneBackendRequest req contentType res accept)
-> f Params -> f (NeptuneBackendRequest req contentType res accept)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Params -> f Params
f Params
rParams
{-# INLINE rParamsL #-}

-- | 'rParams' Lens
rAuthTypesL :: Lens_' (NeptuneBackendRequest req contentType res accept) [P.TypeRep]
rAuthTypesL :: ([TypeRep] -> f [TypeRep])
-> NeptuneBackendRequest req contentType res accept
-> f (NeptuneBackendRequest req contentType res accept)
rAuthTypesL [TypeRep] -> f [TypeRep]
f NeptuneBackendRequest{[TypeRep]
[ByteString]
Method
Params
rAuthTypes :: [TypeRep]
rParams :: Params
rUrlPath :: [ByteString]
rMethod :: Method
rAuthTypes :: forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> [TypeRep]
rParams :: forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> Params
rUrlPath :: forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> [ByteString]
rMethod :: forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> Method
..} = (\[TypeRep]
rAuthTypes -> NeptuneBackendRequest :: forall req contentType res accept.
Method
-> [ByteString]
-> Params
-> [TypeRep]
-> NeptuneBackendRequest req contentType res accept
NeptuneBackendRequest { [TypeRep]
rAuthTypes :: [TypeRep]
rAuthTypes :: [TypeRep]
rAuthTypes, [ByteString]
Method
Params
rParams :: Params
rUrlPath :: [ByteString]
rMethod :: Method
rParams :: Params
rUrlPath :: [ByteString]
rMethod :: Method
..} ) ([TypeRep] -> NeptuneBackendRequest req contentType res accept)
-> f [TypeRep]
-> f (NeptuneBackendRequest req contentType res accept)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TypeRep] -> f [TypeRep]
f [TypeRep]
rAuthTypes
{-# INLINE rAuthTypesL #-}

-- * HasBodyParam

-- | Designates the body parameter of a request
class HasBodyParam req param where
  setBodyParam :: forall contentType res accept. (Consumes req contentType, MimeRender contentType param) => NeptuneBackendRequest req contentType res accept -> param -> NeptuneBackendRequest req contentType res accept
  setBodyParam NeptuneBackendRequest req contentType res accept
req param
xs =
    NeptuneBackendRequest req contentType res accept
req NeptuneBackendRequest req contentType res accept
-> ByteString -> NeptuneBackendRequest req contentType res accept
forall req contentType res accept.
NeptuneBackendRequest req contentType res accept
-> ByteString -> NeptuneBackendRequest req contentType res accept
`_setBodyLBS` Proxy contentType -> param -> ByteString
forall mtype x.
MimeRender mtype x =>
Proxy mtype -> x -> ByteString
mimeRender (Proxy contentType
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy contentType) param
xs NeptuneBackendRequest req contentType res accept
-> (NeptuneBackendRequest req contentType res accept
    -> NeptuneBackendRequest req contentType res accept)
-> NeptuneBackendRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& NeptuneBackendRequest req contentType res accept
-> NeptuneBackendRequest req contentType res accept
forall req contentType res accept.
MimeType contentType =>
NeptuneBackendRequest req contentType res accept
-> NeptuneBackendRequest req contentType res accept
_setContentTypeHeader

-- * HasOptionalParam

-- | Designates the optional parameters of a request
class HasOptionalParam req param where
  {-# MINIMAL applyOptionalParam | (-&-) #-}

  -- | Apply an optional parameter to a request
  applyOptionalParam :: NeptuneBackendRequest req contentType res accept -> param -> NeptuneBackendRequest req contentType res accept
  applyOptionalParam = NeptuneBackendRequest req contentType res accept
-> param -> NeptuneBackendRequest req contentType res accept
forall req param contentType res accept.
HasOptionalParam req param =>
NeptuneBackendRequest req contentType res accept
-> param -> NeptuneBackendRequest req contentType res accept
(-&-)
  {-# INLINE applyOptionalParam #-}

  -- | infix operator \/ alias for 'addOptionalParam'
  (-&-) :: NeptuneBackendRequest req contentType res accept -> param -> NeptuneBackendRequest req contentType res accept
  (-&-) = NeptuneBackendRequest req contentType res accept
-> param -> NeptuneBackendRequest req contentType res accept
forall req param contentType res accept.
HasOptionalParam req param =>
NeptuneBackendRequest req contentType res accept
-> param -> NeptuneBackendRequest req contentType res accept
applyOptionalParam
  {-# INLINE (-&-) #-}

infixl 2 -&-

-- | Request Params
data Params = Params
  { Params -> Query
paramsQuery   :: NH.Query
  , Params -> RequestHeaders
paramsHeaders :: NH.RequestHeaders
  , Params -> ParamBody
paramsBody    :: ParamBody
  }
  deriving (Int -> Params -> ShowS
[Params] -> ShowS
Params -> String
(Int -> Params -> ShowS)
-> (Params -> String) -> ([Params] -> ShowS) -> Show Params
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)

-- | 'paramsQuery' Lens
paramsQueryL :: Lens_' Params NH.Query
paramsQueryL :: (Query -> f Query) -> Params -> f Params
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 -> RequestHeaders -> ParamBody -> Params
Params { Query
paramsQuery :: Query
paramsQuery :: Query
paramsQuery, RequestHeaders
ParamBody
paramsBody :: ParamBody
paramsHeaders :: RequestHeaders
paramsBody :: ParamBody
paramsHeaders :: RequestHeaders
..} ) (Query -> Params) -> f Query -> f Params
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Query -> f Query
f Query
paramsQuery
{-# INLINE paramsQueryL #-}

-- | 'paramsHeaders' Lens
paramsHeadersL :: Lens_' Params NH.RequestHeaders
paramsHeadersL :: (RequestHeaders -> f RequestHeaders) -> Params -> f Params
paramsHeadersL 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 :: Query -> RequestHeaders -> ParamBody -> Params
Params { RequestHeaders
paramsHeaders :: RequestHeaders
paramsHeaders :: RequestHeaders
paramsHeaders, Query
ParamBody
paramsBody :: ParamBody
paramsQuery :: Query
paramsBody :: ParamBody
paramsQuery :: Query
..} ) (RequestHeaders -> Params) -> f RequestHeaders -> f Params
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RequestHeaders -> f RequestHeaders
f RequestHeaders
paramsHeaders
{-# INLINE paramsHeadersL #-}

-- | 'paramsBody' Lens
paramsBodyL :: Lens_' Params ParamBody
paramsBodyL :: (ParamBody -> f ParamBody) -> Params -> f Params
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 :: Query -> RequestHeaders -> ParamBody -> Params
Params { ParamBody
paramsBody :: ParamBody
paramsBody :: ParamBody
paramsBody, Query
RequestHeaders
paramsHeaders :: RequestHeaders
paramsQuery :: Query
paramsHeaders :: RequestHeaders
paramsQuery :: Query
..} ) (ParamBody -> Params) -> f ParamBody -> f Params
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParamBody -> f ParamBody
f ParamBody
paramsBody
{-# INLINE paramsBodyL #-}

-- | Request Body
data ParamBody
  = ParamBodyNone
  | ParamBodyB B.ByteString
  | ParamBodyBL BL.ByteString
  | ParamBodyFormUrlEncoded WH.Form
  | ParamBodyMultipartFormData [NH.Part]
  deriving (Int -> ParamBody -> ShowS
[ParamBody] -> ShowS
ParamBody -> String
(Int -> ParamBody -> ShowS)
-> (ParamBody -> String)
-> ([ParamBody] -> ShowS)
-> Show ParamBody
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)

-- ** NeptuneBackendRequest Utils

_mkRequest :: NH.Method -- ^ Method
          -> [BCL.ByteString] -- ^ Endpoint
          -> NeptuneBackendRequest req contentType res accept -- ^ req: Request Type, res: Response Type
_mkRequest :: Method
-> [ByteString] -> NeptuneBackendRequest req contentType res accept
_mkRequest Method
m [ByteString]
u = Method
-> [ByteString]
-> Params
-> [TypeRep]
-> NeptuneBackendRequest req contentType res accept
forall req contentType res accept.
Method
-> [ByteString]
-> Params
-> [TypeRep]
-> NeptuneBackendRequest req contentType res accept
NeptuneBackendRequest Method
m [ByteString]
u Params
_mkParams []

_mkParams :: Params
_mkParams :: Params
_mkParams = Query -> RequestHeaders -> ParamBody -> Params
Params [] [] ParamBody
ParamBodyNone

setHeader ::
     NeptuneBackendRequest req contentType res accept
  -> [NH.Header]
  -> NeptuneBackendRequest req contentType res accept
setHeader :: NeptuneBackendRequest req contentType res accept
-> RequestHeaders
-> NeptuneBackendRequest req contentType res accept
setHeader NeptuneBackendRequest req contentType res accept
req RequestHeaders
header =
  NeptuneBackendRequest req contentType res accept
req NeptuneBackendRequest req contentType res accept
-> [HeaderName] -> NeptuneBackendRequest req contentType res accept
forall req contentType res accept.
NeptuneBackendRequest req contentType res accept
-> [HeaderName] -> NeptuneBackendRequest req contentType res accept
`removeHeader` ((HeaderName, Method) -> HeaderName)
-> RequestHeaders -> [HeaderName]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.fmap (HeaderName, Method) -> HeaderName
forall a b. (a, b) -> a
P.fst RequestHeaders
header
  NeptuneBackendRequest req contentType res accept
-> (NeptuneBackendRequest req contentType res accept
    -> NeptuneBackendRequest req contentType res accept)
-> NeptuneBackendRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& (NeptuneBackendRequest req contentType res accept
-> RequestHeaders
-> NeptuneBackendRequest req contentType res accept
forall req contentType res accept.
NeptuneBackendRequest req contentType res accept
-> RequestHeaders
-> NeptuneBackendRequest req contentType res accept
`addHeader` RequestHeaders
header)

addHeader ::
     NeptuneBackendRequest req contentType res accept
  -> [NH.Header]
  -> NeptuneBackendRequest req contentType res accept
addHeader :: NeptuneBackendRequest req contentType res accept
-> RequestHeaders
-> NeptuneBackendRequest req contentType res accept
addHeader NeptuneBackendRequest req contentType res accept
req RequestHeaders
header = ASetter
  (NeptuneBackendRequest req contentType res accept)
  (NeptuneBackendRequest req contentType res accept)
  RequestHeaders
  RequestHeaders
-> (RequestHeaders -> RequestHeaders)
-> NeptuneBackendRequest req contentType res accept
-> NeptuneBackendRequest req contentType res accept
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
L.over ((Params -> Identity Params)
-> NeptuneBackendRequest req contentType res accept
-> Identity (NeptuneBackendRequest req contentType res accept)
forall req contentType res accept.
Lens_' (NeptuneBackendRequest req contentType res accept) Params
rParamsL ((Params -> Identity Params)
 -> NeptuneBackendRequest req contentType res accept
 -> Identity (NeptuneBackendRequest req contentType res accept))
-> ((RequestHeaders -> Identity RequestHeaders)
    -> Params -> Identity Params)
-> ASetter
     (NeptuneBackendRequest req contentType res accept)
     (NeptuneBackendRequest req contentType res accept)
     RequestHeaders
     RequestHeaders
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RequestHeaders -> Identity RequestHeaders)
-> Params -> Identity Params
Lens_' Params RequestHeaders
paramsHeadersL) (RequestHeaders
header RequestHeaders -> RequestHeaders -> RequestHeaders
forall a. [a] -> [a] -> [a]
P.++) NeptuneBackendRequest req contentType res accept
req

removeHeader :: NeptuneBackendRequest req contentType res accept -> [NH.HeaderName] -> NeptuneBackendRequest req contentType res accept
removeHeader :: NeptuneBackendRequest req contentType res accept
-> [HeaderName] -> NeptuneBackendRequest req contentType res accept
removeHeader NeptuneBackendRequest req contentType res accept
req [HeaderName]
header =
  NeptuneBackendRequest req contentType res accept
req NeptuneBackendRequest req contentType res accept
-> (NeptuneBackendRequest req contentType res accept
    -> NeptuneBackendRequest req contentType res accept)
-> NeptuneBackendRequest req contentType res accept
forall a b. a -> (a -> b) -> b
&
  ASetter
  (NeptuneBackendRequest req contentType res accept)
  (NeptuneBackendRequest req contentType res accept)
  RequestHeaders
  RequestHeaders
-> (RequestHeaders -> RequestHeaders)
-> NeptuneBackendRequest req contentType res accept
-> NeptuneBackendRequest req contentType res accept
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
L.over
    ((Params -> Identity Params)
-> NeptuneBackendRequest req contentType res accept
-> Identity (NeptuneBackendRequest req contentType res accept)
forall req contentType res accept.
Lens_' (NeptuneBackendRequest req contentType res accept) Params
rParamsL ((Params -> Identity Params)
 -> NeptuneBackendRequest req contentType res accept
 -> Identity (NeptuneBackendRequest req contentType res accept))
-> ((RequestHeaders -> Identity RequestHeaders)
    -> Params -> Identity Params)
-> ASetter
     (NeptuneBackendRequest req contentType res accept)
     (NeptuneBackendRequest req contentType res accept)
     RequestHeaders
     RequestHeaders
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RequestHeaders -> Identity RequestHeaders)
-> Params -> Identity Params
Lens_' Params RequestHeaders
paramsHeadersL)
    (((HeaderName, Method) -> Bool) -> RequestHeaders -> RequestHeaders
forall a. (a -> Bool) -> [a] -> [a]
P.filter (\(HeaderName, Method)
h -> (HeaderName, Method) -> CI HeaderName
forall b. (HeaderName, b) -> CI HeaderName
cifst (HeaderName, Method)
h CI HeaderName -> [CI HeaderName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`P.notElem` (HeaderName -> CI HeaderName) -> [HeaderName] -> [CI HeaderName]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.fmap HeaderName -> CI HeaderName
forall s. FoldCase s => s -> CI s
CI.mk [HeaderName]
header))
  where
    cifst :: (HeaderName, b) -> CI HeaderName
cifst = HeaderName -> CI HeaderName
forall s. FoldCase s => s -> CI s
CI.mk (HeaderName -> CI HeaderName)
-> ((HeaderName, b) -> HeaderName)
-> (HeaderName, b)
-> CI HeaderName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HeaderName, b) -> HeaderName
forall a b. (a, b) -> a
P.fst


_setContentTypeHeader :: forall req contentType res accept. MimeType contentType => NeptuneBackendRequest req contentType res accept -> NeptuneBackendRequest req contentType res accept
_setContentTypeHeader :: NeptuneBackendRequest req contentType res accept
-> NeptuneBackendRequest req contentType res accept
_setContentTypeHeader NeptuneBackendRequest req contentType res accept
req =
    case Proxy contentType -> Maybe MediaType
forall mtype. MimeType mtype => Proxy mtype -> Maybe MediaType
mimeType (Proxy contentType
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy contentType) of
        Just MediaType
m  -> NeptuneBackendRequest req contentType res accept
req NeptuneBackendRequest req contentType res accept
-> RequestHeaders
-> NeptuneBackendRequest req contentType res accept
forall req contentType res accept.
NeptuneBackendRequest req contentType res accept
-> RequestHeaders
-> NeptuneBackendRequest req contentType res accept
`setHeader` [(HeaderName
"content-type", String -> Method
BC.pack (String -> Method) -> String -> Method
forall a b. (a -> b) -> a -> b
$ MediaType -> String
forall a. Show a => a -> String
P.show MediaType
m)]
        Maybe MediaType
Nothing -> NeptuneBackendRequest req contentType res accept
req NeptuneBackendRequest req contentType res accept
-> [HeaderName] -> NeptuneBackendRequest req contentType res accept
forall req contentType res accept.
NeptuneBackendRequest req contentType res accept
-> [HeaderName] -> NeptuneBackendRequest req contentType res accept
`removeHeader` [HeaderName
"content-type"]

_setAcceptHeader :: forall req contentType res accept. MimeType accept => NeptuneBackendRequest req contentType res accept -> NeptuneBackendRequest req contentType res accept
_setAcceptHeader :: NeptuneBackendRequest req contentType res accept
-> NeptuneBackendRequest req contentType res accept
_setAcceptHeader NeptuneBackendRequest req contentType res accept
req =
    case Proxy accept -> Maybe MediaType
forall mtype. MimeType mtype => Proxy mtype -> Maybe MediaType
mimeType (Proxy accept
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy accept) of
        Just MediaType
m  -> NeptuneBackendRequest req contentType res accept
req NeptuneBackendRequest req contentType res accept
-> RequestHeaders
-> NeptuneBackendRequest req contentType res accept
forall req contentType res accept.
NeptuneBackendRequest req contentType res accept
-> RequestHeaders
-> NeptuneBackendRequest req contentType res accept
`setHeader` [(HeaderName
"accept", String -> Method
BC.pack (String -> Method) -> String -> Method
forall a b. (a -> b) -> a -> b
$ MediaType -> String
forall a. Show a => a -> String
P.show MediaType
m)]
        Maybe MediaType
Nothing -> NeptuneBackendRequest req contentType res accept
req NeptuneBackendRequest req contentType res accept
-> [HeaderName] -> NeptuneBackendRequest req contentType res accept
forall req contentType res accept.
NeptuneBackendRequest req contentType res accept
-> [HeaderName] -> NeptuneBackendRequest req contentType res accept
`removeHeader` [HeaderName
"accept"]

setQuery ::
     NeptuneBackendRequest req contentType res accept
  -> [NH.QueryItem]
  -> NeptuneBackendRequest req contentType res accept
setQuery :: NeptuneBackendRequest req contentType res accept
-> Query -> NeptuneBackendRequest req contentType res accept
setQuery NeptuneBackendRequest req contentType res accept
req Query
query =
  NeptuneBackendRequest req contentType res accept
req NeptuneBackendRequest req contentType res accept
-> (NeptuneBackendRequest req contentType res accept
    -> NeptuneBackendRequest req contentType res accept)
-> NeptuneBackendRequest req contentType res accept
forall a b. a -> (a -> b) -> b
&
  ASetter
  (NeptuneBackendRequest req contentType res accept)
  (NeptuneBackendRequest req contentType res accept)
  Query
  Query
-> (Query -> Query)
-> NeptuneBackendRequest req contentType res accept
-> NeptuneBackendRequest req contentType res accept
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
L.over
    ((Params -> Identity Params)
-> NeptuneBackendRequest req contentType res accept
-> Identity (NeptuneBackendRequest req contentType res accept)
forall req contentType res accept.
Lens_' (NeptuneBackendRequest req contentType res accept) Params
rParamsL ((Params -> Identity Params)
 -> NeptuneBackendRequest req contentType res accept
 -> Identity (NeptuneBackendRequest req contentType res accept))
-> ((Query -> Identity Query) -> Params -> Identity Params)
-> ASetter
     (NeptuneBackendRequest req contentType res accept)
     (NeptuneBackendRequest req contentType res accept)
     Query
     Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Query -> Identity Query) -> Params -> Identity Params
Lens_' Params Query
paramsQueryL)
    (((Method, Maybe Method) -> Bool) -> Query -> Query
forall a. (a -> Bool) -> [a] -> [a]
P.filter (\(Method, Maybe Method)
q -> (Method, Maybe Method) -> HeaderName
forall b. (Method, b) -> HeaderName
cifst (Method, Maybe Method)
q HeaderName -> [HeaderName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`P.notElem` ((Method, Maybe Method) -> HeaderName) -> Query -> [HeaderName]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.fmap (Method, Maybe Method) -> HeaderName
forall b. (Method, b) -> HeaderName
cifst Query
query)) NeptuneBackendRequest req contentType res accept
-> (NeptuneBackendRequest req contentType res accept
    -> NeptuneBackendRequest req contentType res accept)
-> NeptuneBackendRequest req contentType res accept
forall a b. a -> (a -> b) -> b
&
  (NeptuneBackendRequest req contentType res accept
-> Query -> NeptuneBackendRequest req contentType res accept
forall req contentType res accept.
NeptuneBackendRequest req contentType res accept
-> Query -> NeptuneBackendRequest req contentType res accept
`addQuery` Query
query)
  where
    cifst :: (Method, b) -> HeaderName
cifst = Method -> HeaderName
forall s. FoldCase s => s -> CI s
CI.mk (Method -> HeaderName)
-> ((Method, b) -> Method) -> (Method, b) -> HeaderName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Method, b) -> Method
forall a b. (a, b) -> a
P.fst

addQuery ::
     NeptuneBackendRequest req contentType res accept
  -> [NH.QueryItem]
  -> NeptuneBackendRequest req contentType res accept
addQuery :: NeptuneBackendRequest req contentType res accept
-> Query -> NeptuneBackendRequest req contentType res accept
addQuery NeptuneBackendRequest req contentType res accept
req Query
query = NeptuneBackendRequest req contentType res accept
req NeptuneBackendRequest req contentType res accept
-> (NeptuneBackendRequest req contentType res accept
    -> NeptuneBackendRequest req contentType res accept)
-> NeptuneBackendRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& ASetter
  (NeptuneBackendRequest req contentType res accept)
  (NeptuneBackendRequest req contentType res accept)
  Query
  Query
-> (Query -> Query)
-> NeptuneBackendRequest req contentType res accept
-> NeptuneBackendRequest req contentType res accept
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
L.over ((Params -> Identity Params)
-> NeptuneBackendRequest req contentType res accept
-> Identity (NeptuneBackendRequest req contentType res accept)
forall req contentType res accept.
Lens_' (NeptuneBackendRequest req contentType res accept) Params
rParamsL ((Params -> Identity Params)
 -> NeptuneBackendRequest req contentType res accept
 -> Identity (NeptuneBackendRequest req contentType res accept))
-> ((Query -> Identity Query) -> Params -> Identity Params)
-> ASetter
     (NeptuneBackendRequest req contentType res accept)
     (NeptuneBackendRequest req contentType res accept)
     Query
     Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Query -> Identity Query) -> Params -> Identity Params
Lens_' Params Query
paramsQueryL) (Query
query Query -> Query -> Query
forall a. [a] -> [a] -> [a]
P.++)

addForm :: NeptuneBackendRequest req contentType res accept -> WH.Form -> NeptuneBackendRequest req contentType res accept
addForm :: NeptuneBackendRequest req contentType res accept
-> Form -> NeptuneBackendRequest req contentType res accept
addForm NeptuneBackendRequest req contentType res accept
req Form
newform =
    let form :: Form
form = case Params -> ParamBody
paramsBody (NeptuneBackendRequest req contentType res accept -> Params
forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> Params
rParams NeptuneBackendRequest req contentType res accept
req) of
            ParamBodyFormUrlEncoded Form
_form -> Form
_form
            ParamBody
_                             -> Form
forall a. Monoid a => a
mempty
    in NeptuneBackendRequest req contentType res accept
req NeptuneBackendRequest req contentType res accept
-> (NeptuneBackendRequest req contentType res accept
    -> NeptuneBackendRequest req contentType res accept)
-> NeptuneBackendRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& ASetter
  (NeptuneBackendRequest req contentType res accept)
  (NeptuneBackendRequest req contentType res accept)
  ParamBody
  ParamBody
-> ParamBody
-> NeptuneBackendRequest req contentType res accept
-> NeptuneBackendRequest req contentType res accept
forall s t a b. ASetter s t a b -> b -> s -> t
L.set ((Params -> Identity Params)
-> NeptuneBackendRequest req contentType res accept
-> Identity (NeptuneBackendRequest req contentType res accept)
forall req contentType res accept.
Lens_' (NeptuneBackendRequest req contentType res accept) Params
rParamsL ((Params -> Identity Params)
 -> NeptuneBackendRequest req contentType res accept
 -> Identity (NeptuneBackendRequest req contentType res accept))
-> ((ParamBody -> Identity ParamBody) -> Params -> Identity Params)
-> ASetter
     (NeptuneBackendRequest req contentType res accept)
     (NeptuneBackendRequest req contentType res accept)
     ParamBody
     ParamBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParamBody -> Identity ParamBody) -> Params -> Identity Params
Lens_' Params ParamBody
paramsBodyL) (Form -> ParamBody
ParamBodyFormUrlEncoded (Form
newform Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> Form
form))

_addMultiFormPart :: NeptuneBackendRequest req contentType res accept -> NH.Part -> NeptuneBackendRequest req contentType res accept
_addMultiFormPart :: NeptuneBackendRequest req contentType res accept
-> Part -> NeptuneBackendRequest req contentType res accept
_addMultiFormPart NeptuneBackendRequest req contentType res accept
req Part
newpart =
    let parts :: [Part]
parts = case Params -> ParamBody
paramsBody (NeptuneBackendRequest req contentType res accept -> Params
forall req contentType res accept.
NeptuneBackendRequest req contentType res accept -> Params
rParams NeptuneBackendRequest req contentType res accept
req) of
            ParamBodyMultipartFormData [Part]
_parts -> [Part]
_parts
            ParamBody
_                                 -> []
    in NeptuneBackendRequest req contentType res accept
req NeptuneBackendRequest req contentType res accept
-> (NeptuneBackendRequest req contentType res accept
    -> NeptuneBackendRequest req contentType res accept)
-> NeptuneBackendRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& ASetter
  (NeptuneBackendRequest req contentType res accept)
  (NeptuneBackendRequest req contentType res accept)
  ParamBody
  ParamBody
-> ParamBody
-> NeptuneBackendRequest req contentType res accept
-> NeptuneBackendRequest req contentType res accept
forall s t a b. ASetter s t a b -> b -> s -> t
L.set ((Params -> Identity Params)
-> NeptuneBackendRequest req contentType res accept
-> Identity (NeptuneBackendRequest req contentType res accept)
forall req contentType res accept.
Lens_' (NeptuneBackendRequest req contentType res accept) Params
rParamsL ((Params -> Identity Params)
 -> NeptuneBackendRequest req contentType res accept
 -> Identity (NeptuneBackendRequest req contentType res accept))
-> ((ParamBody -> Identity ParamBody) -> Params -> Identity Params)
-> ASetter
     (NeptuneBackendRequest req contentType res accept)
     (NeptuneBackendRequest req contentType res accept)
     ParamBody
     ParamBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParamBody -> Identity ParamBody) -> Params -> Identity Params
Lens_' Params ParamBody
paramsBodyL) ([Part] -> ParamBody
ParamBodyMultipartFormData (Part
newpart Part -> [Part] -> [Part]
forall a. a -> [a] -> [a]
: [Part]
parts))

_setBodyBS :: NeptuneBackendRequest req contentType res accept -> B.ByteString -> NeptuneBackendRequest req contentType res accept
_setBodyBS :: NeptuneBackendRequest req contentType res accept
-> Method -> NeptuneBackendRequest req contentType res accept
_setBodyBS NeptuneBackendRequest req contentType res accept
req Method
body =
    NeptuneBackendRequest req contentType res accept
req NeptuneBackendRequest req contentType res accept
-> (NeptuneBackendRequest req contentType res accept
    -> NeptuneBackendRequest req contentType res accept)
-> NeptuneBackendRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& ASetter
  (NeptuneBackendRequest req contentType res accept)
  (NeptuneBackendRequest req contentType res accept)
  ParamBody
  ParamBody
-> ParamBody
-> NeptuneBackendRequest req contentType res accept
-> NeptuneBackendRequest req contentType res accept
forall s t a b. ASetter s t a b -> b -> s -> t
L.set ((Params -> Identity Params)
-> NeptuneBackendRequest req contentType res accept
-> Identity (NeptuneBackendRequest req contentType res accept)
forall req contentType res accept.
Lens_' (NeptuneBackendRequest req contentType res accept) Params
rParamsL ((Params -> Identity Params)
 -> NeptuneBackendRequest req contentType res accept
 -> Identity (NeptuneBackendRequest req contentType res accept))
-> ((ParamBody -> Identity ParamBody) -> Params -> Identity Params)
-> ASetter
     (NeptuneBackendRequest req contentType res accept)
     (NeptuneBackendRequest req contentType res accept)
     ParamBody
     ParamBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParamBody -> Identity ParamBody) -> Params -> Identity Params
Lens_' Params ParamBody
paramsBodyL) (Method -> ParamBody
ParamBodyB Method
body)

_setBodyLBS :: NeptuneBackendRequest req contentType res accept -> BL.ByteString -> NeptuneBackendRequest req contentType res accept
_setBodyLBS :: NeptuneBackendRequest req contentType res accept
-> ByteString -> NeptuneBackendRequest req contentType res accept
_setBodyLBS NeptuneBackendRequest req contentType res accept
req ByteString
body =
    NeptuneBackendRequest req contentType res accept
req NeptuneBackendRequest req contentType res accept
-> (NeptuneBackendRequest req contentType res accept
    -> NeptuneBackendRequest req contentType res accept)
-> NeptuneBackendRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& ASetter
  (NeptuneBackendRequest req contentType res accept)
  (NeptuneBackendRequest req contentType res accept)
  ParamBody
  ParamBody
-> ParamBody
-> NeptuneBackendRequest req contentType res accept
-> NeptuneBackendRequest req contentType res accept
forall s t a b. ASetter s t a b -> b -> s -> t
L.set ((Params -> Identity Params)
-> NeptuneBackendRequest req contentType res accept
-> Identity (NeptuneBackendRequest req contentType res accept)
forall req contentType res accept.
Lens_' (NeptuneBackendRequest req contentType res accept) Params
rParamsL ((Params -> Identity Params)
 -> NeptuneBackendRequest req contentType res accept
 -> Identity (NeptuneBackendRequest req contentType res accept))
-> ((ParamBody -> Identity ParamBody) -> Params -> Identity Params)
-> ASetter
     (NeptuneBackendRequest req contentType res accept)
     (NeptuneBackendRequest req contentType res accept)
     ParamBody
     ParamBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParamBody -> Identity ParamBody) -> Params -> Identity Params
Lens_' Params ParamBody
paramsBodyL) (ByteString -> ParamBody
ParamBodyBL ByteString
body)

_hasAuthType :: AuthMethod authMethod => NeptuneBackendRequest req contentType res accept -> P.Proxy authMethod -> NeptuneBackendRequest req contentType res accept
_hasAuthType :: NeptuneBackendRequest req contentType res accept
-> Proxy authMethod
-> NeptuneBackendRequest req contentType res accept
_hasAuthType NeptuneBackendRequest req contentType res accept
req Proxy authMethod
proxy =
  NeptuneBackendRequest req contentType res accept
req NeptuneBackendRequest req contentType res accept
-> (NeptuneBackendRequest req contentType res accept
    -> NeptuneBackendRequest req contentType res accept)
-> NeptuneBackendRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& ASetter
  (NeptuneBackendRequest req contentType res accept)
  (NeptuneBackendRequest req contentType res accept)
  [TypeRep]
  [TypeRep]
-> ([TypeRep] -> [TypeRep])
-> NeptuneBackendRequest req contentType res accept
-> NeptuneBackendRequest req contentType res accept
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
L.over ASetter
  (NeptuneBackendRequest req contentType res accept)
  (NeptuneBackendRequest req contentType res accept)
  [TypeRep]
  [TypeRep]
forall req contentType res accept.
Lens_' (NeptuneBackendRequest req contentType res accept) [TypeRep]
rAuthTypesL (Proxy authMethod -> TypeRep
forall k (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
P.typeRep Proxy authMethod
proxy TypeRep -> [TypeRep] -> [TypeRep]
forall a. a -> [a] -> [a]
:)

-- ** Params Utils

toPath
  :: WH.ToHttpApiData a
  => a -> BCL.ByteString
toPath :: a -> ByteString
toPath = Builder -> ByteString
BB.toLazyByteString (Builder -> ByteString) -> (a -> Builder) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Builder
forall a. ToHttpApiData a => a -> Builder
WH.toEncodedUrlPiece

toHeader :: WH.ToHttpApiData a => (NH.HeaderName, a) -> [NH.Header]
toHeader :: (HeaderName, a) -> RequestHeaders
toHeader (HeaderName, a)
x = [(a -> Method) -> (HeaderName, a) -> (HeaderName, Method)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Method
forall a. ToHttpApiData a => a -> Method
WH.toHeader (HeaderName, a)
x]

toForm :: WH.ToHttpApiData v => (BC.ByteString, v) -> WH.Form
toForm :: (Method, v) -> Form
toForm (Method
k,v
v) = [(String, v)] -> Form
forall a. ToForm a => a -> Form
WH.toForm [(Method -> String
BC.unpack Method
k,v
v)]

toQuery :: WH.ToHttpApiData a => (BC.ByteString, Maybe a) -> [NH.QueryItem]
toQuery :: (Method, Maybe a) -> Query
toQuery (Method, Maybe a)
x = [((Maybe a -> Maybe Method)
-> (Method, Maybe a) -> (Method, Maybe Method)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Maybe a -> Maybe Method)
 -> (Method, Maybe a) -> (Method, Maybe Method))
-> ((a -> Method) -> Maybe a -> Maybe Method)
-> (a -> Method)
-> (Method, Maybe a)
-> (Method, Maybe Method)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Method) -> Maybe a -> Maybe Method
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) a -> Method
toQueryParam (Method, Maybe a)
x]
  where toQueryParam :: a -> Method
toQueryParam = Text -> Method
T.encodeUtf8 (Text -> Method) -> (a -> Text) -> a -> Method
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. ToHttpApiData a => a -> Text
WH.toQueryParam

-- *** OpenAPI `CollectionFormat` Utils

-- | Determines the format of the array if type array is used.
data CollectionFormat
  = CommaSeparated -- ^ CSV format for multiple parameters.
  | SpaceSeparated -- ^ Also called "SSV"
  | TabSeparated -- ^ Also called "TSV"
  | PipeSeparated -- ^ `value1|value2|value2`
  | MultiParamArray -- ^ Using multiple GET parameters, e.g. `foo=bar&foo=baz`. This is valid only for parameters in "query" ('NH.Query') or "formData" ('WH.Form')

toHeaderColl :: WH.ToHttpApiData a => CollectionFormat -> (NH.HeaderName, [a]) -> [NH.Header]
toHeaderColl :: CollectionFormat -> (HeaderName, [a]) -> RequestHeaders
toHeaderColl CollectionFormat
c (HeaderName, [a])
xs = CollectionFormat
-> ((HeaderName, a) -> RequestHeaders)
-> (HeaderName, [a])
-> RequestHeaders
forall (f :: * -> *) a b.
Traversable f =>
CollectionFormat
-> (f a -> [(b, Method)]) -> f [a] -> [(b, Method)]
_toColl CollectionFormat
c (HeaderName, a) -> RequestHeaders
forall a. ToHttpApiData a => (HeaderName, a) -> RequestHeaders
toHeader (HeaderName, [a])
xs

toFormColl :: WH.ToHttpApiData v => CollectionFormat -> (BC.ByteString, [v]) -> WH.Form
toFormColl :: CollectionFormat -> (Method, [v]) -> Form
toFormColl CollectionFormat
c (Method, [v])
xs = [(String, String)] -> Form
forall a. ToForm a => a -> Form
WH.toForm ([(String, String)] -> Form) -> [(String, String)] -> Form
forall a b. (a -> b) -> a -> b
$ ((HeaderName, Method) -> (String, String))
-> RequestHeaders -> [(String, String)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (HeaderName, Method) -> (String, String)
unpack (RequestHeaders -> [(String, String)])
-> RequestHeaders -> [(String, String)]
forall a b. (a -> b) -> a -> b
$ CollectionFormat
-> ((HeaderName, v) -> RequestHeaders)
-> (HeaderName, [v])
-> RequestHeaders
forall (f :: * -> *) a b.
Traversable f =>
CollectionFormat
-> (f a -> [(b, Method)]) -> f [a] -> [(b, Method)]
_toColl CollectionFormat
c (HeaderName, v) -> RequestHeaders
forall a. ToHttpApiData a => (HeaderName, a) -> RequestHeaders
toHeader ((HeaderName, [v]) -> RequestHeaders)
-> (HeaderName, [v]) -> RequestHeaders
forall a b. (a -> b) -> a -> b
$ (Method, [v]) -> (HeaderName, [v])
forall s b. FoldCase s => (s, b) -> (CI s, b)
pack (Method, [v])
xs
  where
    pack :: (s, b) -> (CI s, b)
pack (s
k,b
v) = (s -> CI s
forall s. FoldCase s => s -> CI s
CI.mk s
k, b
v)
    unpack :: (HeaderName, Method) -> (String, String)
unpack (HeaderName
k,Method
v) = (Method -> String
BC.unpack (HeaderName -> Method
forall s. CI s -> s
CI.original HeaderName
k), Method -> String
BC.unpack Method
v)

toQueryColl :: WH.ToHttpApiData a => CollectionFormat -> (BC.ByteString, Maybe [a]) -> NH.Query
toQueryColl :: CollectionFormat -> (Method, Maybe [a]) -> Query
toQueryColl CollectionFormat
c (Method, Maybe [a])
xs = CollectionFormat
-> ((Method, Maybe a) -> Query) -> (Method, Maybe [a]) -> Query
forall (f :: * -> *) (t :: * -> *) a b.
(Traversable f, Traversable t, Alternative t) =>
CollectionFormat
-> (f (t a) -> [(b, t Method)]) -> f (t [a]) -> [(b, t Method)]
_toCollA CollectionFormat
c (Method, Maybe a) -> Query
forall a. ToHttpApiData a => (Method, Maybe a) -> Query
toQuery (Method, Maybe [a])
xs

_toColl :: P.Traversable f => CollectionFormat -> (f a -> [(b, BC.ByteString)]) -> f [a] -> [(b, BC.ByteString)]
_toColl :: CollectionFormat
-> (f a -> [(b, Method)]) -> f [a] -> [(b, Method)]
_toColl CollectionFormat
c f a -> [(b, Method)]
encode f [a]
xs = ((b, Maybe Method) -> (b, Method))
-> [(b, Maybe Method)] -> [(b, Method)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Maybe Method -> Method) -> (b, Maybe Method) -> (b, Method)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe Method -> Method
forall a. HasCallStack => Maybe a -> a
P.fromJust) (CollectionFormat
-> (f (Maybe a) -> [(b, Maybe Method)])
-> (Char -> Method)
-> f (Maybe [a])
-> [(b, Maybe Method)]
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 Method)]
fencode Char -> Method
BC.singleton (([a] -> Maybe [a]) -> f [a] -> f (Maybe [a])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [a] -> Maybe [a]
forall a. a -> Maybe a
Just f [a]
xs))
  where fencode :: f (Maybe a) -> [(b, Maybe Method)]
fencode = ((b, Method) -> (b, Maybe Method))
-> [(b, Method)] -> [(b, Maybe Method)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Method -> Maybe Method) -> (b, Method) -> (b, Maybe Method)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Method -> Maybe Method
forall a. a -> Maybe a
Just) ([(b, Method)] -> [(b, Maybe Method)])
-> (f (Maybe a) -> [(b, Method)])
-> f (Maybe a)
-> [(b, Maybe Method)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> [(b, Method)]
encode (f a -> [(b, Method)])
-> (f (Maybe a) -> f a) -> f (Maybe a) -> [(b, Method)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe a -> a) -> f (Maybe a) -> f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe a -> a
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 :: CollectionFormat
-> (f (t a) -> [(b, t Method)]) -> f (t [a]) -> [(b, t Method)]
_toCollA CollectionFormat
c f (t a) -> [(b, t Method)]
encode f (t [a])
xs = CollectionFormat
-> (f (t a) -> [(b, t Method)])
-> (Char -> Method)
-> f (t [a])
-> [(b, t Method)]
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 Method)]
encode Char -> Method
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' :: 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 =
      [((b, t c) -> (b, t c) -> (b, t c)) -> [(b, t c)] -> (b, t c)
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
P.foldl1 (\(b
sk, t c
sv) (b
_, t c
v) -> (b
sk, (c -> c -> c -> c
forall a. Semigroup a => a -> a -> a -> a
combine c
sep (c -> c -> c) -> t c -> t (c -> c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> t c
sv t (c -> c) -> t c -> t c
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> t c
v) t c -> t c -> t c
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> t c
sv t c -> t c -> t c
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 a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
sep a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
y
    expandList :: [(b, t c)]
expandList = ((f (t a) -> [(b, t c)]) -> [f (t a)] -> [(b, t c)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
P.concatMap f (t a) -> [(b, t c)]
encode ([f (t a)] -> [(b, t c)])
-> (f (t [a]) -> [f (t a)]) -> f (t [a]) -> [(b, t c)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((t [a] -> [t a]) -> f (t [a]) -> [f (t a)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
P.traverse ((t [a] -> [t a]) -> f (t [a]) -> [f (t a)])
-> (([a] -> [a]) -> t [a] -> [t a])
-> ([a] -> [a])
-> f (t [a])
-> [f (t a)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([a] -> [a]) -> t [a] -> [t a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
P.traverse) [a] -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
P.toList) f (t [a])
xs
    {-# INLINE go #-}
    {-# INLINE expandList #-}
    {-# INLINE combine #-}

-- * AuthMethods

-- | Provides a method to apply auth methods to requests
class P.Typeable a =>
      AuthMethod a  where
  applyAuthMethod
    :: NeptuneBackendConfig
    -> a
    -> NeptuneBackendRequest req contentType res accept
    -> IO (NeptuneBackendRequest req contentType res accept)

-- | An existential wrapper for any AuthMethod
data AnyAuthMethod = forall a. AuthMethod a => AnyAuthMethod a deriving (P.Typeable)

instance AuthMethod AnyAuthMethod where applyAuthMethod :: NeptuneBackendConfig
-> AnyAuthMethod
-> NeptuneBackendRequest req contentType res accept
-> IO (NeptuneBackendRequest req contentType res accept)
applyAuthMethod NeptuneBackendConfig
config (AnyAuthMethod a
a) NeptuneBackendRequest req contentType res accept
req = NeptuneBackendConfig
-> a
-> NeptuneBackendRequest req contentType res accept
-> IO (NeptuneBackendRequest req contentType res accept)
forall a req contentType res accept.
AuthMethod a =>
NeptuneBackendConfig
-> a
-> NeptuneBackendRequest req contentType res accept
-> IO (NeptuneBackendRequest req contentType res accept)
applyAuthMethod NeptuneBackendConfig
config a
a NeptuneBackendRequest req contentType res accept
req

-- | indicates exceptions related to AuthMethods
data AuthMethodException = AuthMethodException String deriving (Int -> AuthMethodException -> ShowS
[AuthMethodException] -> ShowS
AuthMethodException -> String
(Int -> AuthMethodException -> ShowS)
-> (AuthMethodException -> String)
-> ([AuthMethodException] -> ShowS)
-> Show AuthMethodException
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

-- | apply all matching AuthMethods in config to request
_applyAuthMethods
  :: NeptuneBackendRequest req contentType res accept
  -> NeptuneBackendConfig
  -> IO (NeptuneBackendRequest req contentType res accept)
_applyAuthMethods :: NeptuneBackendRequest req contentType res accept
-> NeptuneBackendConfig
-> IO (NeptuneBackendRequest req contentType res accept)
_applyAuthMethods NeptuneBackendRequest req contentType res accept
req config :: NeptuneBackendConfig
config@(NeptuneBackendConfig {configAuthMethods :: NeptuneBackendConfig -> [AnyAuthMethod]
configAuthMethods = [AnyAuthMethod]
as}) =
  (NeptuneBackendRequest req contentType res accept
 -> AnyAuthMethod
 -> IO (NeptuneBackendRequest req contentType res accept))
-> NeptuneBackendRequest req contentType res accept
-> [AnyAuthMethod]
-> IO (NeptuneBackendRequest req contentType res accept)
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldlM NeptuneBackendRequest req contentType res accept
-> AnyAuthMethod
-> IO (NeptuneBackendRequest req contentType res accept)
go NeptuneBackendRequest req contentType res accept
req [AnyAuthMethod]
as
  where
    go :: NeptuneBackendRequest req contentType res accept
-> AnyAuthMethod
-> IO (NeptuneBackendRequest req contentType res accept)
go NeptuneBackendRequest req contentType res accept
r (AnyAuthMethod a
a) = NeptuneBackendConfig
-> a
-> NeptuneBackendRequest req contentType res accept
-> IO (NeptuneBackendRequest req contentType res accept)
forall a req contentType res accept.
AuthMethod a =>
NeptuneBackendConfig
-> a
-> NeptuneBackendRequest req contentType res accept
-> IO (NeptuneBackendRequest req contentType res accept)
applyAuthMethod NeptuneBackendConfig
config a
a NeptuneBackendRequest req contentType res accept
r

-- * Utils

-- | Removes Null fields.  (OpenAPI-Specification 2.0 does not allow Null in JSON)
_omitNulls :: [(Text, A.Value)] -> A.Value
_omitNulls :: [(Text, Value)] -> Value
_omitNulls = [(Text, Value)] -> Value
A.object ([(Text, Value)] -> Value)
-> ([(Text, Value)] -> [(Text, Value)]) -> [(Text, Value)] -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Text, Value) -> Bool) -> [(Text, Value)] -> [(Text, Value)]
forall a. (a -> Bool) -> [a] -> [a]
P.filter (Text, Value) -> Bool
forall a. (a, Value) -> Bool
notNull
  where
    notNull :: (a, Value) -> Bool
notNull (a
_, Value
A.Null) = Bool
False
    notNull (a, Value)
_           = Bool
True

-- | Encodes fields using WH.toQueryParam
_toFormItem :: (WH.ToHttpApiData a, Functor f) => t -> f a -> f (t, [Text])
_toFormItem :: t -> f a -> f (t, [Text])
_toFormItem t
name f a
x = (t
name,) ([Text] -> (t, [Text])) -> (a -> [Text]) -> a -> (t, [Text])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[]) (Text -> [Text]) -> (a -> Text) -> a -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. ToHttpApiData a => a -> Text
WH.toQueryParam (a -> (t, [Text])) -> f a -> f (t, [Text])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f a
x

-- | Collapse (Just "") to Nothing
_emptyToNothing :: Maybe String -> Maybe String
_emptyToNothing :: Maybe String -> Maybe String
_emptyToNothing (Just String
"") = Maybe String
forall a. Maybe a
Nothing
_emptyToNothing Maybe String
x         = Maybe String
x
{-# INLINE _emptyToNothing #-}

-- | Collapse (Just mempty) to Nothing
_memptyToNothing :: (P.Monoid a, P.Eq a) => Maybe a -> Maybe a
_memptyToNothing :: Maybe a -> Maybe a
_memptyToNothing (Just a
x) | a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
P.== a
forall a. Monoid a => a
P.mempty = Maybe a
forall a. Maybe a
Nothing
_memptyToNothing Maybe a
x = Maybe a
x
{-# INLINE _memptyToNothing #-}

-- * DateTime Formatting

newtype DateTime = DateTime { DateTime -> UTCTime
unDateTime :: TI.UTCTime }
  deriving (DateTime -> DateTime -> Bool
(DateTime -> DateTime -> Bool)
-> (DateTime -> DateTime -> Bool) -> Eq DateTime
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
DataType
Constr
Typeable DateTime
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> DateTime -> c DateTime)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c DateTime)
-> (DateTime -> Constr)
-> (DateTime -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> DateTime -> DateTime)
-> (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 u. (forall d. Data d => d -> u) -> DateTime -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> DateTime -> u)
-> (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 (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> DateTime -> m DateTime)
-> Data DateTime
DateTime -> DataType
DateTime -> Constr
(forall b. Data b => b -> b) -> DateTime -> DateTime
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DateTime -> c DateTime
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cDateTime :: Constr
$tDateTime :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> DateTime -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DateTime -> u
gmapQ :: (forall d. Data d => d -> u) -> DateTime -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> DateTime -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable DateTime
P.Data,Eq DateTime
Eq DateTime
-> (DateTime -> DateTime -> Ordering)
-> (DateTime -> DateTime -> Bool)
-> (DateTime -> DateTime -> Bool)
-> (DateTime -> DateTime -> Bool)
-> (DateTime -> DateTime -> Bool)
-> (DateTime -> DateTime -> DateTime)
-> (DateTime -> DateTime -> DateTime)
-> Ord 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
$cp1Ord :: Eq DateTime
P.Ord,P.Typeable,DateTime -> ()
(DateTime -> ()) -> NFData DateTime
forall a. (a -> ()) -> NFData a
rnf :: DateTime -> ()
$crnf :: DateTime -> ()
NF.NFData)
instance A.FromJSON DateTime where
  parseJSON :: Value -> Parser DateTime
parseJSON = String -> (Text -> Parser DateTime) -> Value -> Parser DateTime
forall a. String -> (Text -> Parser a) -> Value -> Parser a
A.withText String
"DateTime" (String -> Parser DateTime
forall (m :: * -> *).
(MonadFail m, Alternative m) =>
String -> m DateTime
_readDateTime (String -> Parser DateTime)
-> (Text -> String) -> Text -> Parser DateTime
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) = String -> Value
forall a. ToJSON a => a -> Value
A.toJSON (UTCTime -> String
forall t. (t ~ UTCTime, FormatTime t) => t -> String
_showDateTime UTCTime
t)
instance WH.FromHttpApiData DateTime where
  parseUrlPiece :: Text -> Either Text DateTime
parseUrlPiece = Either Text DateTime
-> (DateTime -> Either Text DateTime)
-> Maybe DateTime
-> Either Text DateTime
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Text -> Either Text DateTime
forall a b. a -> Either a b
P.Left Text
"parseUrlPiece @DateTime") DateTime -> Either Text DateTime
forall a b. b -> Either a b
P.Right (Maybe DateTime -> Either Text DateTime)
-> (Text -> Maybe DateTime) -> Text -> Either Text DateTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe DateTime
forall (m :: * -> *).
(MonadFail m, Alternative m) =>
String -> m DateTime
_readDateTime (String -> Maybe DateTime)
-> (Text -> String) -> Text -> Maybe DateTime
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 (UTCTime -> String
forall t. (t ~ UTCTime, FormatTime t) => t -> String
_showDateTime UTCTime
t)
instance P.Show DateTime where
  show :: DateTime -> String
show (DateTime UTCTime
t) = UTCTime -> String
forall t. (t ~ UTCTime, FormatTime t) => t -> String
_showDateTime UTCTime
t
instance MimeRender MimeMultipartFormData DateTime where
  mimeRender :: Proxy MimeMultipartFormData -> DateTime -> ByteString
mimeRender Proxy MimeMultipartFormData
_ = DateTime -> ByteString
forall a. ToHttpApiData a => a -> ByteString
mimeRenderDefaultMultipartFormData

-- | @_parseISO8601@
_readDateTime :: (MonadFail m, Alternative m) => String -> m DateTime
_readDateTime :: String -> m DateTime
_readDateTime String
s =
  UTCTime -> DateTime
DateTime (UTCTime -> DateTime) -> m UTCTime -> m DateTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> m UTCTime
forall t (m :: * -> *).
(ParseTime t, MonadFail m, Alternative m) =>
String -> m t
_parseISO8601 String
s
{-# INLINE _readDateTime #-}

-- | @TI.formatISO8601Millis@
_showDateTime :: (t ~ TI.UTCTime, TI.FormatTime t) => t -> String
_showDateTime :: t -> String
_showDateTime =
  t -> String
UTCTime -> String
TI.formatISO8601Millis
{-# INLINE _showDateTime #-}

-- | parse an ISO8601 date-time string
_parseISO8601 :: (TI.ParseTime t, MonadFail m, Alternative m) => String -> m t
_parseISO8601 :: String -> m t
_parseISO8601 String
t =
  [m t] -> m t
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
P.asum ([m t] -> m t) -> [m t] -> m t
forall a b. (a -> b) -> a -> b
$
  (String -> String -> m t) -> String -> String -> m t
forall a b c. (a -> b -> c) -> b -> a -> c
P.flip (Bool -> TimeLocale -> String -> String -> m t
forall (m :: * -> *) t.
(MonadFail m, ParseTime t) =>
Bool -> TimeLocale -> String -> String -> m t
TI.parseTimeM Bool
True TimeLocale
TI.defaultTimeLocale) String
t (String -> m t) -> [String] -> [m 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 #-}

-- * Date Formatting

newtype Date = Date { Date -> Day
unDate :: TI.Day }
  deriving (Int -> Date
Date -> Int
Date -> [Date]
Date -> Date
Date -> Date -> [Date]
Date -> Date -> Date -> [Date]
(Date -> Date)
-> (Date -> Date)
-> (Int -> Date)
-> (Date -> Int)
-> (Date -> [Date])
-> (Date -> Date -> [Date])
-> (Date -> Date -> [Date])
-> (Date -> Date -> Date -> [Date])
-> Enum 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
(Date -> Date -> Bool) -> (Date -> Date -> Bool) -> Eq Date
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
DataType
Constr
Typeable Date
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Date -> c Date)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Date)
-> (Date -> Constr)
-> (Date -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> Date -> Date)
-> (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 u. (forall d. Data d => d -> u) -> Date -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Date -> u)
-> (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 (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Date -> m Date)
-> Data Date
Date -> DataType
Date -> Constr
(forall b. Data b => b -> b) -> Date -> Date
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Date -> c Date
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cDate :: Constr
$tDate :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> Date -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Date -> u
gmapQ :: (forall d. Data d => d -> u) -> Date -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Date -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable Date
P.Data,Eq Date
Eq Date
-> (Date -> Date -> Ordering)
-> (Date -> Date -> Bool)
-> (Date -> Date -> Bool)
-> (Date -> Date -> Bool)
-> (Date -> Date -> Bool)
-> (Date -> Date -> Date)
-> (Date -> Date -> Date)
-> Ord 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
$cp1Ord :: Eq Date
P.Ord,Ord Date
Ord Date
-> ((Date, Date) -> [Date])
-> ((Date, Date) -> Date -> Int)
-> ((Date, Date) -> Date -> Int)
-> ((Date, Date) -> Date -> Bool)
-> ((Date, Date) -> Int)
-> ((Date, Date) -> Int)
-> Ix 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]
$cp1Ix :: Ord Date
P.Ix,Date -> ()
(Date -> ()) -> NFData Date
forall a. (a -> ()) -> NFData a
rnf :: Date -> ()
$crnf :: Date -> ()
NF.NFData)
instance A.FromJSON Date where
  parseJSON :: Value -> Parser Date
parseJSON = String -> (Text -> Parser Date) -> Value -> Parser Date
forall a. String -> (Text -> Parser a) -> Value -> Parser a
A.withText String
"Date" (String -> Parser Date
forall (m :: * -> *). MonadFail m => String -> m Date
_readDate (String -> Parser Date) -> (Text -> String) -> Text -> Parser Date
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) = String -> Value
forall a. ToJSON a => a -> Value
A.toJSON (Day -> String
forall t. FormatTime t => t -> String
_showDate Day
t)
instance WH.FromHttpApiData Date where
  parseUrlPiece :: Text -> Either Text Date
parseUrlPiece = Either Text Date
-> (Date -> Either Text Date) -> Maybe Date -> Either Text Date
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Text -> Either Text Date
forall a b. a -> Either a b
P.Left Text
"parseUrlPiece @Date") Date -> Either Text Date
forall a b. b -> Either a b
P.Right (Maybe Date -> Either Text Date)
-> (Text -> Maybe Date) -> Text -> Either Text Date
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe Date
forall (m :: * -> *). MonadFail m => String -> m Date
_readDate (String -> Maybe Date) -> (Text -> String) -> Text -> Maybe Date
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 (Day -> String
forall t. FormatTime t => t -> String
_showDate Day
t)
instance P.Show Date where
  show :: Date -> String
show (Date Day
t) = Day -> String
forall t. FormatTime t => t -> String
_showDate Day
t
instance MimeRender MimeMultipartFormData Date where
  mimeRender :: Proxy MimeMultipartFormData -> Date -> ByteString
mimeRender Proxy MimeMultipartFormData
_ = Date -> ByteString
forall a. ToHttpApiData a => a -> ByteString
mimeRenderDefaultMultipartFormData

-- | @TI.parseTimeM True TI.defaultTimeLocale "%Y-%m-%d"@
_readDate :: MonadFail m => String -> m Date
_readDate :: String -> m Date
_readDate String
s = Day -> Date
Date (Day -> Date) -> m Day -> m Date
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool -> TimeLocale -> String -> String -> m Day
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 #-}

-- | @TI.formatTime TI.defaultTimeLocale "%Y-%m-%d"@
_showDate :: TI.FormatTime t => t -> String
_showDate :: t -> String
_showDate =
  TimeLocale -> String -> t -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
TI.formatTime TimeLocale
TI.defaultTimeLocale String
"%Y-%m-%d"
{-# INLINE _showDate #-}

-- * Byte/Binary Formatting


-- | base64 encoded characters
newtype ByteArray = ByteArray { ByteArray -> ByteString
unByteArray :: BL.ByteString }
  deriving (ByteArray -> ByteArray -> Bool
(ByteArray -> ByteArray -> Bool)
-> (ByteArray -> ByteArray -> Bool) -> Eq ByteArray
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
DataType
Constr
Typeable ByteArray
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> ByteArray -> c ByteArray)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ByteArray)
-> (ByteArray -> Constr)
-> (ByteArray -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> ByteArray -> ByteArray)
-> (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 u. (forall d. Data d => d -> u) -> ByteArray -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ByteArray -> u)
-> (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 (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ByteArray -> m ByteArray)
-> Data ByteArray
ByteArray -> DataType
ByteArray -> Constr
(forall b. Data b => b -> b) -> ByteArray -> ByteArray
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ByteArray -> c ByteArray
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cByteArray :: Constr
$tByteArray :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> ByteArray -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ByteArray -> u
gmapQ :: (forall d. Data d => d -> u) -> ByteArray -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ByteArray -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable ByteArray
P.Data,Eq ByteArray
Eq ByteArray
-> (ByteArray -> ByteArray -> Ordering)
-> (ByteArray -> ByteArray -> Bool)
-> (ByteArray -> ByteArray -> Bool)
-> (ByteArray -> ByteArray -> Bool)
-> (ByteArray -> ByteArray -> Bool)
-> (ByteArray -> ByteArray -> ByteArray)
-> (ByteArray -> ByteArray -> ByteArray)
-> Ord 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
$cp1Ord :: Eq ByteArray
P.Ord,P.Typeable,ByteArray -> ()
(ByteArray -> ()) -> NFData ByteArray
forall a. (a -> ()) -> NFData a
rnf :: ByteArray -> ()
$crnf :: ByteArray -> ()
NF.NFData)

instance A.FromJSON ByteArray where
  parseJSON :: Value -> Parser ByteArray
parseJSON = String -> (Text -> Parser ByteArray) -> Value -> Parser ByteArray
forall a. String -> (Text -> Parser a) -> Value -> Parser a
A.withText String
"ByteArray" Text -> Parser ByteArray
forall (m :: * -> *). MonadFail m => Text -> m ByteArray
_readByteArray
instance A.ToJSON ByteArray where
  toJSON :: ByteArray -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
A.toJSON (Text -> Value) -> (ByteArray -> Text) -> ByteArray -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteArray -> Text
_showByteArray
instance WH.FromHttpApiData ByteArray where
  parseUrlPiece :: Text -> Either Text ByteArray
parseUrlPiece = Either Text ByteArray
-> (ByteArray -> Either Text ByteArray)
-> Maybe ByteArray
-> Either Text ByteArray
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Text -> Either Text ByteArray
forall a b. a -> Either a b
P.Left Text
"parseUrlPiece @ByteArray") ByteArray -> Either Text ByteArray
forall a b. b -> Either a b
P.Right (Maybe ByteArray -> Either Text ByteArray)
-> (Text -> Maybe ByteArray) -> Text -> Either Text ByteArray
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe ByteArray
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 (Text -> String) -> (ByteArray -> Text) -> ByteArray -> String
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
_ = ByteArray -> ByteString
forall a. ToHttpApiData a => a -> ByteString
mimeRenderDefaultMultipartFormData

-- | read base64 encoded characters
_readByteArray :: MonadFail m => Text -> m ByteArray
_readByteArray :: Text -> m ByteArray
_readByteArray = (String -> m ByteArray)
-> (ByteString -> m ByteArray)
-> Either String ByteString
-> m ByteArray
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
P.either String -> m ByteArray
forall (m :: * -> *) a. MonadFail m => String -> m a
P.fail (ByteArray -> m ByteArray
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteArray -> m ByteArray)
-> (ByteString -> ByteArray) -> ByteString -> m ByteArray
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteArray
ByteArray) (Either String ByteString -> m ByteArray)
-> (Text -> Either String ByteString) -> Text -> m ByteArray
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String ByteString
BL64.decode (ByteString -> Either String ByteString)
-> (Text -> ByteString) -> Text -> Either String ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> ByteString
BL.fromStrict (Method -> ByteString) -> (Text -> Method) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Method
T.encodeUtf8
{-# INLINE _readByteArray #-}

-- | show base64 encoded characters
_showByteArray :: ByteArray -> Text
_showByteArray :: ByteArray -> Text
_showByteArray = Method -> Text
T.decodeUtf8 (Method -> Text) -> (ByteArray -> Method) -> ByteArray -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Method
BL.toStrict (ByteString -> Method)
-> (ByteArray -> ByteString) -> ByteArray -> Method
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL64.encode (ByteString -> ByteString)
-> (ByteArray -> ByteString) -> ByteArray -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteArray -> ByteString
unByteArray
{-# INLINE _showByteArray #-}

-- | any sequence of octets
newtype Binary = Binary { Binary -> ByteString
unBinary :: BL.ByteString }
  deriving (Binary -> Binary -> Bool
(Binary -> Binary -> Bool)
-> (Binary -> Binary -> Bool) -> Eq Binary
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
DataType
Constr
Typeable Binary
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Binary -> c Binary)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Binary)
-> (Binary -> Constr)
-> (Binary -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> Binary -> Binary)
-> (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 u. (forall d. Data d => d -> u) -> Binary -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Binary -> u)
-> (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 (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Binary -> m Binary)
-> Data Binary
Binary -> DataType
Binary -> Constr
(forall b. Data b => b -> b) -> Binary -> Binary
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binary -> c Binary
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cBinary :: Constr
$tBinary :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> Binary -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Binary -> u
gmapQ :: (forall d. Data d => d -> u) -> Binary -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Binary -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable Binary
P.Data,Eq Binary
Eq Binary
-> (Binary -> Binary -> Ordering)
-> (Binary -> Binary -> Bool)
-> (Binary -> Binary -> Bool)
-> (Binary -> Binary -> Bool)
-> (Binary -> Binary -> Bool)
-> (Binary -> Binary -> Binary)
-> (Binary -> Binary -> Binary)
-> Ord 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
$cp1Ord :: Eq Binary
P.Ord,P.Typeable,Binary -> ()
(Binary -> ()) -> NFData Binary
forall a. (a -> ()) -> NFData a
rnf :: Binary -> ()
$crnf :: Binary -> ()
NF.NFData)

instance A.FromJSON Binary where
  parseJSON :: Value -> Parser Binary
parseJSON = String -> (Text -> Parser Binary) -> Value -> Parser Binary
forall a. String -> (Text -> Parser a) -> Value -> Parser a
A.withText String
"Binary" Text -> Parser Binary
forall (m :: * -> *). MonadFail m => Text -> m Binary
_readBinaryBase64
instance A.ToJSON Binary where
  toJSON :: Binary -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
A.toJSON (Text -> Value) -> (Binary -> Text) -> Binary -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Binary -> Text
_showBinaryBase64
instance WH.FromHttpApiData Binary where
  parseUrlPiece :: Text -> Either Text Binary
parseUrlPiece = Either Text Binary
-> (Binary -> Either Text Binary)
-> Maybe Binary
-> Either Text Binary
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Text -> Either Text Binary
forall a b. a -> Either a b
P.Left Text
"parseUrlPiece @Binary") Binary -> Either Text Binary
forall a b. b -> Either a b
P.Right (Maybe Binary -> Either Text Binary)
-> (Text -> Maybe Binary) -> Text -> Either Text Binary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe Binary
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 (Text -> String) -> (Binary -> Text) -> Binary -> String
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 :: Text -> m Binary
_readBinaryBase64 = (String -> m Binary)
-> (ByteString -> m Binary) -> Either String ByteString -> m Binary
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
P.either String -> m Binary
forall (m :: * -> *) a. MonadFail m => String -> m a
P.fail (Binary -> m Binary
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Binary -> m Binary)
-> (ByteString -> Binary) -> ByteString -> m Binary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Binary
Binary) (Either String ByteString -> m Binary)
-> (Text -> Either String ByteString) -> Text -> m Binary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String ByteString
BL64.decode (ByteString -> Either String ByteString)
-> (Text -> ByteString) -> Text -> Either String ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> ByteString
BL.fromStrict (Method -> ByteString) -> (Text -> Method) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Method
T.encodeUtf8
{-# INLINE _readBinaryBase64 #-}

_showBinaryBase64 :: Binary -> Text
_showBinaryBase64 :: Binary -> Text
_showBinaryBase64 = Method -> Text
T.decodeUtf8 (Method -> Text) -> (Binary -> Method) -> Binary -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Method
BL.toStrict (ByteString -> Method)
-> (Binary -> ByteString) -> Binary -> Method
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL64.encode (ByteString -> ByteString)
-> (Binary -> ByteString) -> Binary -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Binary -> ByteString
unBinary
{-# INLINE _showBinaryBase64 #-}

-- * Lens Type Aliases

type Lens_' s a = Lens_ s s a a
type Lens_ s t a b = forall (f :: * -> *). Functor f => (a -> f b) -> s -> f t