{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Servant.Foreign.Internal where
import Prelude ()
import Prelude.Compat
import Control.Lens
(Getter, makeLenses, makePrisms, (%~), (&), (.~), (<>~))
import Data.Data
(Data)
import Data.Proxy
import Data.String
import Data.Text
import Data.Text.Encoding
(decodeUtf8)
import Data.Typeable
(Typeable)
import GHC.TypeLits
import qualified Network.HTTP.Types as HTTP
import Servant.API
import Servant.API.Modifiers
(RequiredArgument)
import Servant.API.TypeLevel
newtype FunctionName = FunctionName { FunctionName -> [Text]
unFunctionName :: [Text] }
deriving (Typeable FunctionName
Typeable FunctionName =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunctionName -> c FunctionName)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunctionName)
-> (FunctionName -> Constr)
-> (FunctionName -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunctionName))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FunctionName))
-> ((forall b. Data b => b -> b) -> FunctionName -> FunctionName)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionName -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionName -> r)
-> (forall u. (forall d. Data d => d -> u) -> FunctionName -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> FunctionName -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName)
-> Data FunctionName
FunctionName -> Constr
FunctionName -> DataType
(forall b. Data b => b -> b) -> FunctionName -> FunctionName
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) -> FunctionName -> u
forall u. (forall d. Data d => d -> u) -> FunctionName -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionName -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionName -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunctionName
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunctionName -> c FunctionName
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunctionName)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FunctionName)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunctionName -> c FunctionName
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunctionName -> c FunctionName
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunctionName
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunctionName
$ctoConstr :: FunctionName -> Constr
toConstr :: FunctionName -> Constr
$cdataTypeOf :: FunctionName -> DataType
dataTypeOf :: FunctionName -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunctionName)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunctionName)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FunctionName)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FunctionName)
$cgmapT :: (forall b. Data b => b -> b) -> FunctionName -> FunctionName
gmapT :: (forall b. Data b => b -> b) -> FunctionName -> FunctionName
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionName -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionName -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionName -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionName -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FunctionName -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> FunctionName -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FunctionName -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FunctionName -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunctionName -> m FunctionName
Data, Int -> FunctionName -> ShowS
[FunctionName] -> ShowS
FunctionName -> String
(Int -> FunctionName -> ShowS)
-> (FunctionName -> String)
-> ([FunctionName] -> ShowS)
-> Show FunctionName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FunctionName -> ShowS
showsPrec :: Int -> FunctionName -> ShowS
$cshow :: FunctionName -> String
show :: FunctionName -> String
$cshowList :: [FunctionName] -> ShowS
showList :: [FunctionName] -> ShowS
Show, FunctionName -> FunctionName -> Bool
(FunctionName -> FunctionName -> Bool)
-> (FunctionName -> FunctionName -> Bool) -> Eq FunctionName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FunctionName -> FunctionName -> Bool
== :: FunctionName -> FunctionName -> Bool
$c/= :: FunctionName -> FunctionName -> Bool
/= :: FunctionName -> FunctionName -> Bool
Eq, NonEmpty FunctionName -> FunctionName
FunctionName -> FunctionName -> FunctionName
(FunctionName -> FunctionName -> FunctionName)
-> (NonEmpty FunctionName -> FunctionName)
-> (forall b. Integral b => b -> FunctionName -> FunctionName)
-> Semigroup FunctionName
forall b. Integral b => b -> FunctionName -> FunctionName
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: FunctionName -> FunctionName -> FunctionName
<> :: FunctionName -> FunctionName -> FunctionName
$csconcat :: NonEmpty FunctionName -> FunctionName
sconcat :: NonEmpty FunctionName -> FunctionName
$cstimes :: forall b. Integral b => b -> FunctionName -> FunctionName
stimes :: forall b. Integral b => b -> FunctionName -> FunctionName
Semigroup, Semigroup FunctionName
FunctionName
Semigroup FunctionName =>
FunctionName
-> (FunctionName -> FunctionName -> FunctionName)
-> ([FunctionName] -> FunctionName)
-> Monoid FunctionName
[FunctionName] -> FunctionName
FunctionName -> FunctionName -> FunctionName
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: FunctionName
mempty :: FunctionName
$cmappend :: FunctionName -> FunctionName -> FunctionName
mappend :: FunctionName -> FunctionName -> FunctionName
$cmconcat :: [FunctionName] -> FunctionName
mconcat :: [FunctionName] -> FunctionName
Monoid, Typeable)
makePrisms ''FunctionName
newtype PathSegment = PathSegment { PathSegment -> Text
unPathSegment :: Text }
deriving (Typeable PathSegment
Typeable PathSegment =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PathSegment -> c PathSegment)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PathSegment)
-> (PathSegment -> Constr)
-> (PathSegment -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PathSegment))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PathSegment))
-> ((forall b. Data b => b -> b) -> PathSegment -> PathSegment)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PathSegment -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PathSegment -> r)
-> (forall u. (forall d. Data d => d -> u) -> PathSegment -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> PathSegment -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PathSegment -> m PathSegment)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathSegment -> m PathSegment)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathSegment -> m PathSegment)
-> Data PathSegment
PathSegment -> Constr
PathSegment -> DataType
(forall b. Data b => b -> b) -> PathSegment -> PathSegment
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) -> PathSegment -> u
forall u. (forall d. Data d => d -> u) -> PathSegment -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PathSegment -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PathSegment -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PathSegment -> m PathSegment
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathSegment -> m PathSegment
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PathSegment
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PathSegment -> c PathSegment
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PathSegment)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PathSegment)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PathSegment -> c PathSegment
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PathSegment -> c PathSegment
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PathSegment
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PathSegment
$ctoConstr :: PathSegment -> Constr
toConstr :: PathSegment -> Constr
$cdataTypeOf :: PathSegment -> DataType
dataTypeOf :: PathSegment -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PathSegment)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PathSegment)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PathSegment)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PathSegment)
$cgmapT :: (forall b. Data b => b -> b) -> PathSegment -> PathSegment
gmapT :: (forall b. Data b => b -> b) -> PathSegment -> PathSegment
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PathSegment -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PathSegment -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PathSegment -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PathSegment -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PathSegment -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> PathSegment -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PathSegment -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PathSegment -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PathSegment -> m PathSegment
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PathSegment -> m PathSegment
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathSegment -> m PathSegment
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathSegment -> m PathSegment
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathSegment -> m PathSegment
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathSegment -> m PathSegment
Data, Int -> PathSegment -> ShowS
[PathSegment] -> ShowS
PathSegment -> String
(Int -> PathSegment -> ShowS)
-> (PathSegment -> String)
-> ([PathSegment] -> ShowS)
-> Show PathSegment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PathSegment -> ShowS
showsPrec :: Int -> PathSegment -> ShowS
$cshow :: PathSegment -> String
show :: PathSegment -> String
$cshowList :: [PathSegment] -> ShowS
showList :: [PathSegment] -> ShowS
Show, PathSegment -> PathSegment -> Bool
(PathSegment -> PathSegment -> Bool)
-> (PathSegment -> PathSegment -> Bool) -> Eq PathSegment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PathSegment -> PathSegment -> Bool
== :: PathSegment -> PathSegment -> Bool
$c/= :: PathSegment -> PathSegment -> Bool
/= :: PathSegment -> PathSegment -> Bool
Eq, String -> PathSegment
(String -> PathSegment) -> IsString PathSegment
forall a. (String -> a) -> IsString a
$cfromString :: String -> PathSegment
fromString :: String -> PathSegment
IsString, NonEmpty PathSegment -> PathSegment
PathSegment -> PathSegment -> PathSegment
(PathSegment -> PathSegment -> PathSegment)
-> (NonEmpty PathSegment -> PathSegment)
-> (forall b. Integral b => b -> PathSegment -> PathSegment)
-> Semigroup PathSegment
forall b. Integral b => b -> PathSegment -> PathSegment
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: PathSegment -> PathSegment -> PathSegment
<> :: PathSegment -> PathSegment -> PathSegment
$csconcat :: NonEmpty PathSegment -> PathSegment
sconcat :: NonEmpty PathSegment -> PathSegment
$cstimes :: forall b. Integral b => b -> PathSegment -> PathSegment
stimes :: forall b. Integral b => b -> PathSegment -> PathSegment
Semigroup, Semigroup PathSegment
PathSegment
Semigroup PathSegment =>
PathSegment
-> (PathSegment -> PathSegment -> PathSegment)
-> ([PathSegment] -> PathSegment)
-> Monoid PathSegment
[PathSegment] -> PathSegment
PathSegment -> PathSegment -> PathSegment
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: PathSegment
mempty :: PathSegment
$cmappend :: PathSegment -> PathSegment -> PathSegment
mappend :: PathSegment -> PathSegment -> PathSegment
$cmconcat :: [PathSegment] -> PathSegment
mconcat :: [PathSegment] -> PathSegment
Monoid, Typeable)
makePrisms ''PathSegment
data Arg ftype = Arg
{ forall ftype. Arg ftype -> PathSegment
_argName :: PathSegment
, forall ftype. Arg ftype -> ftype
_argType :: ftype
}
deriving (Typeable (Arg ftype)
Typeable (Arg ftype) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Arg ftype -> c (Arg ftype))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Arg ftype))
-> (Arg ftype -> Constr)
-> (Arg ftype -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Arg ftype)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Arg ftype)))
-> ((forall b. Data b => b -> b) -> Arg ftype -> Arg ftype)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Arg ftype -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Arg ftype -> r)
-> (forall u. (forall d. Data d => d -> u) -> Arg ftype -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Arg ftype -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Arg ftype -> m (Arg ftype))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Arg ftype -> m (Arg ftype))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Arg ftype -> m (Arg ftype))
-> Data (Arg ftype)
Arg ftype -> Constr
Arg ftype -> DataType
(forall b. Data b => b -> b) -> Arg ftype -> Arg ftype
forall ftype. Data ftype => Typeable (Arg ftype)
forall ftype. Data ftype => Arg ftype -> Constr
forall ftype. Data ftype => Arg ftype -> DataType
forall ftype.
Data ftype =>
(forall b. Data b => b -> b) -> Arg ftype -> Arg ftype
forall ftype u.
Data ftype =>
Int -> (forall d. Data d => d -> u) -> Arg ftype -> u
forall ftype u.
Data ftype =>
(forall d. Data d => d -> u) -> Arg ftype -> [u]
forall ftype r r'.
Data ftype =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Arg ftype -> r
forall ftype r r'.
Data ftype =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Arg ftype -> r
forall ftype (m :: * -> *).
(Data ftype, Monad m) =>
(forall d. Data d => d -> m d) -> Arg ftype -> m (Arg ftype)
forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Arg ftype -> m (Arg ftype)
forall ftype (c :: * -> *).
Data ftype =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Arg ftype)
forall ftype (c :: * -> *).
Data ftype =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Arg ftype -> c (Arg ftype)
forall ftype (t :: * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Arg ftype))
forall ftype (t :: * -> * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Arg ftype))
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) -> Arg ftype -> u
forall u. (forall d. Data d => d -> u) -> Arg ftype -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Arg ftype -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Arg ftype -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Arg ftype -> m (Arg ftype)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Arg ftype -> m (Arg ftype)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Arg ftype)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Arg ftype -> c (Arg ftype)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Arg ftype))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Arg ftype))
$cgfoldl :: forall ftype (c :: * -> *).
Data ftype =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Arg ftype -> c (Arg ftype)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Arg ftype -> c (Arg ftype)
$cgunfold :: forall ftype (c :: * -> *).
Data ftype =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Arg ftype)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Arg ftype)
$ctoConstr :: forall ftype. Data ftype => Arg ftype -> Constr
toConstr :: Arg ftype -> Constr
$cdataTypeOf :: forall ftype. Data ftype => Arg ftype -> DataType
dataTypeOf :: Arg ftype -> DataType
$cdataCast1 :: forall ftype (t :: * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Arg ftype))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Arg ftype))
$cdataCast2 :: forall ftype (t :: * -> * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Arg ftype))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Arg ftype))
$cgmapT :: forall ftype.
Data ftype =>
(forall b. Data b => b -> b) -> Arg ftype -> Arg ftype
gmapT :: (forall b. Data b => b -> b) -> Arg ftype -> Arg ftype
$cgmapQl :: forall ftype r r'.
Data ftype =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Arg ftype -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Arg ftype -> r
$cgmapQr :: forall ftype r r'.
Data ftype =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Arg ftype -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Arg ftype -> r
$cgmapQ :: forall ftype u.
Data ftype =>
(forall d. Data d => d -> u) -> Arg ftype -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Arg ftype -> [u]
$cgmapQi :: forall ftype u.
Data ftype =>
Int -> (forall d. Data d => d -> u) -> Arg ftype -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Arg ftype -> u
$cgmapM :: forall ftype (m :: * -> *).
(Data ftype, Monad m) =>
(forall d. Data d => d -> m d) -> Arg ftype -> m (Arg ftype)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Arg ftype -> m (Arg ftype)
$cgmapMp :: forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Arg ftype -> m (Arg ftype)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Arg ftype -> m (Arg ftype)
$cgmapMo :: forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Arg ftype -> m (Arg ftype)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Arg ftype -> m (Arg ftype)
Data, Arg ftype -> Arg ftype -> Bool
(Arg ftype -> Arg ftype -> Bool)
-> (Arg ftype -> Arg ftype -> Bool) -> Eq (Arg ftype)
forall ftype. Eq ftype => Arg ftype -> Arg ftype -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall ftype. Eq ftype => Arg ftype -> Arg ftype -> Bool
== :: Arg ftype -> Arg ftype -> Bool
$c/= :: forall ftype. Eq ftype => Arg ftype -> Arg ftype -> Bool
/= :: Arg ftype -> Arg ftype -> Bool
Eq, Int -> Arg ftype -> ShowS
[Arg ftype] -> ShowS
Arg ftype -> String
(Int -> Arg ftype -> ShowS)
-> (Arg ftype -> String)
-> ([Arg ftype] -> ShowS)
-> Show (Arg ftype)
forall ftype. Show ftype => Int -> Arg ftype -> ShowS
forall ftype. Show ftype => [Arg ftype] -> ShowS
forall ftype. Show ftype => Arg ftype -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall ftype. Show ftype => Int -> Arg ftype -> ShowS
showsPrec :: Int -> Arg ftype -> ShowS
$cshow :: forall ftype. Show ftype => Arg ftype -> String
show :: Arg ftype -> String
$cshowList :: forall ftype. Show ftype => [Arg ftype] -> ShowS
showList :: [Arg ftype] -> ShowS
Show, Typeable)
makeLenses ''Arg
argPath :: Getter (Arg ftype) Text
argPath :: forall ftype (f :: * -> *).
(Contravariant f, Functor f) =>
(Text -> f Text) -> Arg ftype -> f (Arg ftype)
argPath = (PathSegment -> f PathSegment) -> Arg ftype -> f (Arg ftype)
forall ftype (f :: * -> *).
Functor f =>
(PathSegment -> f PathSegment) -> Arg ftype -> f (Arg ftype)
argName ((PathSegment -> f PathSegment) -> Arg ftype -> f (Arg ftype))
-> ((Text -> f Text) -> PathSegment -> f PathSegment)
-> (Text -> f Text)
-> Arg ftype
-> f (Arg ftype)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> f Text) -> PathSegment -> f PathSegment
Iso' PathSegment Text
_PathSegment
data SegmentType ftype
= Static PathSegment
| Cap (Arg ftype)
deriving (Typeable (SegmentType ftype)
Typeable (SegmentType ftype) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SegmentType ftype
-> c (SegmentType ftype))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (SegmentType ftype))
-> (SegmentType ftype -> Constr)
-> (SegmentType ftype -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (SegmentType ftype)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (SegmentType ftype)))
-> ((forall b. Data b => b -> b)
-> SegmentType ftype -> SegmentType ftype)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SegmentType ftype -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SegmentType ftype -> r)
-> (forall u.
(forall d. Data d => d -> u) -> SegmentType ftype -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> SegmentType ftype -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SegmentType ftype -> m (SegmentType ftype))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SegmentType ftype -> m (SegmentType ftype))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SegmentType ftype -> m (SegmentType ftype))
-> Data (SegmentType ftype)
SegmentType ftype -> Constr
SegmentType ftype -> DataType
(forall b. Data b => b -> b)
-> SegmentType ftype -> SegmentType ftype
forall ftype. Data ftype => Typeable (SegmentType ftype)
forall ftype. Data ftype => SegmentType ftype -> Constr
forall ftype. Data ftype => SegmentType ftype -> DataType
forall ftype.
Data ftype =>
(forall b. Data b => b -> b)
-> SegmentType ftype -> SegmentType ftype
forall ftype u.
Data ftype =>
Int -> (forall d. Data d => d -> u) -> SegmentType ftype -> u
forall ftype u.
Data ftype =>
(forall d. Data d => d -> u) -> SegmentType ftype -> [u]
forall ftype r r'.
Data ftype =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SegmentType ftype -> r
forall ftype r r'.
Data ftype =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SegmentType ftype -> r
forall ftype (m :: * -> *).
(Data ftype, Monad m) =>
(forall d. Data d => d -> m d)
-> SegmentType ftype -> m (SegmentType ftype)
forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> SegmentType ftype -> m (SegmentType ftype)
forall ftype (c :: * -> *).
Data ftype =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (SegmentType ftype)
forall ftype (c :: * -> *).
Data ftype =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SegmentType ftype
-> c (SegmentType ftype)
forall ftype (t :: * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (SegmentType ftype))
forall ftype (t :: * -> * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (SegmentType ftype))
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) -> SegmentType ftype -> u
forall u. (forall d. Data d => d -> u) -> SegmentType ftype -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SegmentType ftype -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SegmentType ftype -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SegmentType ftype -> m (SegmentType ftype)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SegmentType ftype -> m (SegmentType ftype)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (SegmentType ftype)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SegmentType ftype
-> c (SegmentType ftype)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (SegmentType ftype))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (SegmentType ftype))
$cgfoldl :: forall ftype (c :: * -> *).
Data ftype =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SegmentType ftype
-> c (SegmentType ftype)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SegmentType ftype
-> c (SegmentType ftype)
$cgunfold :: forall ftype (c :: * -> *).
Data ftype =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (SegmentType ftype)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (SegmentType ftype)
$ctoConstr :: forall ftype. Data ftype => SegmentType ftype -> Constr
toConstr :: SegmentType ftype -> Constr
$cdataTypeOf :: forall ftype. Data ftype => SegmentType ftype -> DataType
dataTypeOf :: SegmentType ftype -> DataType
$cdataCast1 :: forall ftype (t :: * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (SegmentType ftype))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (SegmentType ftype))
$cdataCast2 :: forall ftype (t :: * -> * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (SegmentType ftype))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (SegmentType ftype))
$cgmapT :: forall ftype.
Data ftype =>
(forall b. Data b => b -> b)
-> SegmentType ftype -> SegmentType ftype
gmapT :: (forall b. Data b => b -> b)
-> SegmentType ftype -> SegmentType ftype
$cgmapQl :: forall ftype r r'.
Data ftype =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SegmentType ftype -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SegmentType ftype -> r
$cgmapQr :: forall ftype r r'.
Data ftype =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SegmentType ftype -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SegmentType ftype -> r
$cgmapQ :: forall ftype u.
Data ftype =>
(forall d. Data d => d -> u) -> SegmentType ftype -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> SegmentType ftype -> [u]
$cgmapQi :: forall ftype u.
Data ftype =>
Int -> (forall d. Data d => d -> u) -> SegmentType ftype -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SegmentType ftype -> u
$cgmapM :: forall ftype (m :: * -> *).
(Data ftype, Monad m) =>
(forall d. Data d => d -> m d)
-> SegmentType ftype -> m (SegmentType ftype)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SegmentType ftype -> m (SegmentType ftype)
$cgmapMp :: forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> SegmentType ftype -> m (SegmentType ftype)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SegmentType ftype -> m (SegmentType ftype)
$cgmapMo :: forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> SegmentType ftype -> m (SegmentType ftype)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SegmentType ftype -> m (SegmentType ftype)
Data, SegmentType ftype -> SegmentType ftype -> Bool
(SegmentType ftype -> SegmentType ftype -> Bool)
-> (SegmentType ftype -> SegmentType ftype -> Bool)
-> Eq (SegmentType ftype)
forall ftype.
Eq ftype =>
SegmentType ftype -> SegmentType ftype -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall ftype.
Eq ftype =>
SegmentType ftype -> SegmentType ftype -> Bool
== :: SegmentType ftype -> SegmentType ftype -> Bool
$c/= :: forall ftype.
Eq ftype =>
SegmentType ftype -> SegmentType ftype -> Bool
/= :: SegmentType ftype -> SegmentType ftype -> Bool
Eq, Int -> SegmentType ftype -> ShowS
[SegmentType ftype] -> ShowS
SegmentType ftype -> String
(Int -> SegmentType ftype -> ShowS)
-> (SegmentType ftype -> String)
-> ([SegmentType ftype] -> ShowS)
-> Show (SegmentType ftype)
forall ftype. Show ftype => Int -> SegmentType ftype -> ShowS
forall ftype. Show ftype => [SegmentType ftype] -> ShowS
forall ftype. Show ftype => SegmentType ftype -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall ftype. Show ftype => Int -> SegmentType ftype -> ShowS
showsPrec :: Int -> SegmentType ftype -> ShowS
$cshow :: forall ftype. Show ftype => SegmentType ftype -> String
show :: SegmentType ftype -> String
$cshowList :: forall ftype. Show ftype => [SegmentType ftype] -> ShowS
showList :: [SegmentType ftype] -> ShowS
Show, Typeable)
makePrisms ''SegmentType
newtype Segment ftype = Segment { forall ftype. Segment ftype -> SegmentType ftype
unSegment :: SegmentType ftype }
deriving (Typeable (Segment ftype)
Typeable (Segment ftype) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Segment ftype -> c (Segment ftype))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Segment ftype))
-> (Segment ftype -> Constr)
-> (Segment ftype -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Segment ftype)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Segment ftype)))
-> ((forall b. Data b => b -> b) -> Segment ftype -> Segment ftype)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Segment ftype -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Segment ftype -> r)
-> (forall u. (forall d. Data d => d -> u) -> Segment ftype -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Segment ftype -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> Segment ftype -> m (Segment ftype))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Segment ftype -> m (Segment ftype))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Segment ftype -> m (Segment ftype))
-> Data (Segment ftype)
Segment ftype -> Constr
Segment ftype -> DataType
(forall b. Data b => b -> b) -> Segment ftype -> Segment ftype
forall ftype. Data ftype => Typeable (Segment ftype)
forall ftype. Data ftype => Segment ftype -> Constr
forall ftype. Data ftype => Segment ftype -> DataType
forall ftype.
Data ftype =>
(forall b. Data b => b -> b) -> Segment ftype -> Segment ftype
forall ftype u.
Data ftype =>
Int -> (forall d. Data d => d -> u) -> Segment ftype -> u
forall ftype u.
Data ftype =>
(forall d. Data d => d -> u) -> Segment ftype -> [u]
forall ftype r r'.
Data ftype =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Segment ftype -> r
forall ftype r r'.
Data ftype =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Segment ftype -> r
forall ftype (m :: * -> *).
(Data ftype, Monad m) =>
(forall d. Data d => d -> m d)
-> Segment ftype -> m (Segment ftype)
forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> Segment ftype -> m (Segment ftype)
forall ftype (c :: * -> *).
Data ftype =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Segment ftype)
forall ftype (c :: * -> *).
Data ftype =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Segment ftype -> c (Segment ftype)
forall ftype (t :: * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Segment ftype))
forall ftype (t :: * -> * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Segment ftype))
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) -> Segment ftype -> u
forall u. (forall d. Data d => d -> u) -> Segment ftype -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Segment ftype -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Segment ftype -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> Segment ftype -> m (Segment ftype)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Segment ftype -> m (Segment ftype)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Segment ftype)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Segment ftype -> c (Segment ftype)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Segment ftype))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Segment ftype))
$cgfoldl :: forall ftype (c :: * -> *).
Data ftype =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Segment ftype -> c (Segment ftype)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Segment ftype -> c (Segment ftype)
$cgunfold :: forall ftype (c :: * -> *).
Data ftype =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Segment ftype)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Segment ftype)
$ctoConstr :: forall ftype. Data ftype => Segment ftype -> Constr
toConstr :: Segment ftype -> Constr
$cdataTypeOf :: forall ftype. Data ftype => Segment ftype -> DataType
dataTypeOf :: Segment ftype -> DataType
$cdataCast1 :: forall ftype (t :: * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Segment ftype))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Segment ftype))
$cdataCast2 :: forall ftype (t :: * -> * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Segment ftype))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Segment ftype))
$cgmapT :: forall ftype.
Data ftype =>
(forall b. Data b => b -> b) -> Segment ftype -> Segment ftype
gmapT :: (forall b. Data b => b -> b) -> Segment ftype -> Segment ftype
$cgmapQl :: forall ftype r r'.
Data ftype =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Segment ftype -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Segment ftype -> r
$cgmapQr :: forall ftype r r'.
Data ftype =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Segment ftype -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Segment ftype -> r
$cgmapQ :: forall ftype u.
Data ftype =>
(forall d. Data d => d -> u) -> Segment ftype -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Segment ftype -> [u]
$cgmapQi :: forall ftype u.
Data ftype =>
Int -> (forall d. Data d => d -> u) -> Segment ftype -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Segment ftype -> u
$cgmapM :: forall ftype (m :: * -> *).
(Data ftype, Monad m) =>
(forall d. Data d => d -> m d)
-> Segment ftype -> m (Segment ftype)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> Segment ftype -> m (Segment ftype)
$cgmapMp :: forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> Segment ftype -> m (Segment ftype)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Segment ftype -> m (Segment ftype)
$cgmapMo :: forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> Segment ftype -> m (Segment ftype)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Segment ftype -> m (Segment ftype)
Data, Segment ftype -> Segment ftype -> Bool
(Segment ftype -> Segment ftype -> Bool)
-> (Segment ftype -> Segment ftype -> Bool) -> Eq (Segment ftype)
forall ftype. Eq ftype => Segment ftype -> Segment ftype -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall ftype. Eq ftype => Segment ftype -> Segment ftype -> Bool
== :: Segment ftype -> Segment ftype -> Bool
$c/= :: forall ftype. Eq ftype => Segment ftype -> Segment ftype -> Bool
/= :: Segment ftype -> Segment ftype -> Bool
Eq, Int -> Segment ftype -> ShowS
[Segment ftype] -> ShowS
Segment ftype -> String
(Int -> Segment ftype -> ShowS)
-> (Segment ftype -> String)
-> ([Segment ftype] -> ShowS)
-> Show (Segment ftype)
forall ftype. Show ftype => Int -> Segment ftype -> ShowS
forall ftype. Show ftype => [Segment ftype] -> ShowS
forall ftype. Show ftype => Segment ftype -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall ftype. Show ftype => Int -> Segment ftype -> ShowS
showsPrec :: Int -> Segment ftype -> ShowS
$cshow :: forall ftype. Show ftype => Segment ftype -> String
show :: Segment ftype -> String
$cshowList :: forall ftype. Show ftype => [Segment ftype] -> ShowS
showList :: [Segment ftype] -> ShowS
Show, Typeable)
makePrisms ''Segment
isCapture :: Segment ftype -> Bool
isCapture :: forall ftype. Segment ftype -> Bool
isCapture (Segment (Cap Arg ftype
_)) = Bool
True
isCapture Segment ftype
_ = Bool
False
captureArg :: Segment ftype -> Arg ftype
captureArg :: forall ftype. Segment ftype -> Arg ftype
captureArg (Segment (Cap Arg ftype
s)) = Arg ftype
s
captureArg Segment ftype
_ = String -> Arg ftype
forall a. HasCallStack => String -> a
error String
"captureArg called on non capture"
type Path ftype = [Segment ftype]
data ArgType
= Normal
| Flag
| List
deriving (Typeable ArgType
Typeable ArgType =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ArgType -> c ArgType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ArgType)
-> (ArgType -> Constr)
-> (ArgType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ArgType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArgType))
-> ((forall b. Data b => b -> b) -> ArgType -> ArgType)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ArgType -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ArgType -> r)
-> (forall u. (forall d. Data d => d -> u) -> ArgType -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> ArgType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ArgType -> m ArgType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ArgType -> m ArgType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ArgType -> m ArgType)
-> Data ArgType
ArgType -> Constr
ArgType -> DataType
(forall b. Data b => b -> b) -> ArgType -> ArgType
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) -> ArgType -> u
forall u. (forall d. Data d => d -> u) -> ArgType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ArgType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ArgType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ArgType -> m ArgType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ArgType -> m ArgType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ArgType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ArgType -> c ArgType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ArgType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArgType)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ArgType -> c ArgType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ArgType -> c ArgType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ArgType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ArgType
$ctoConstr :: ArgType -> Constr
toConstr :: ArgType -> Constr
$cdataTypeOf :: ArgType -> DataType
dataTypeOf :: ArgType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ArgType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ArgType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArgType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArgType)
$cgmapT :: (forall b. Data b => b -> b) -> ArgType -> ArgType
gmapT :: (forall b. Data b => b -> b) -> ArgType -> ArgType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ArgType -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ArgType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ArgType -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ArgType -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ArgType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ArgType -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ArgType -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ArgType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ArgType -> m ArgType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ArgType -> m ArgType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ArgType -> m ArgType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ArgType -> m ArgType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ArgType -> m ArgType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ArgType -> m ArgType
Data, ArgType -> ArgType -> Bool
(ArgType -> ArgType -> Bool)
-> (ArgType -> ArgType -> Bool) -> Eq ArgType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ArgType -> ArgType -> Bool
== :: ArgType -> ArgType -> Bool
$c/= :: ArgType -> ArgType -> Bool
/= :: ArgType -> ArgType -> Bool
Eq, Int -> ArgType -> ShowS
[ArgType] -> ShowS
ArgType -> String
(Int -> ArgType -> ShowS)
-> (ArgType -> String) -> ([ArgType] -> ShowS) -> Show ArgType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ArgType -> ShowS
showsPrec :: Int -> ArgType -> ShowS
$cshow :: ArgType -> String
show :: ArgType -> String
$cshowList :: [ArgType] -> ShowS
showList :: [ArgType] -> ShowS
Show, Typeable)
makePrisms ''ArgType
data QueryArg ftype = QueryArg
{ forall ftype. QueryArg ftype -> Arg ftype
_queryArgName :: Arg ftype
, forall ftype. QueryArg ftype -> ArgType
_queryArgType :: ArgType
}
deriving (Typeable (QueryArg ftype)
Typeable (QueryArg ftype) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QueryArg ftype -> c (QueryArg ftype))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (QueryArg ftype))
-> (QueryArg ftype -> Constr)
-> (QueryArg ftype -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (QueryArg ftype)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (QueryArg ftype)))
-> ((forall b. Data b => b -> b)
-> QueryArg ftype -> QueryArg ftype)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QueryArg ftype -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QueryArg ftype -> r)
-> (forall u.
(forall d. Data d => d -> u) -> QueryArg ftype -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> QueryArg ftype -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> QueryArg ftype -> m (QueryArg ftype))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> QueryArg ftype -> m (QueryArg ftype))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> QueryArg ftype -> m (QueryArg ftype))
-> Data (QueryArg ftype)
QueryArg ftype -> Constr
QueryArg ftype -> DataType
(forall b. Data b => b -> b) -> QueryArg ftype -> QueryArg ftype
forall ftype. Data ftype => Typeable (QueryArg ftype)
forall ftype. Data ftype => QueryArg ftype -> Constr
forall ftype. Data ftype => QueryArg ftype -> DataType
forall ftype.
Data ftype =>
(forall b. Data b => b -> b) -> QueryArg ftype -> QueryArg ftype
forall ftype u.
Data ftype =>
Int -> (forall d. Data d => d -> u) -> QueryArg ftype -> u
forall ftype u.
Data ftype =>
(forall d. Data d => d -> u) -> QueryArg ftype -> [u]
forall ftype r r'.
Data ftype =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QueryArg ftype -> r
forall ftype r r'.
Data ftype =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QueryArg ftype -> r
forall ftype (m :: * -> *).
(Data ftype, Monad m) =>
(forall d. Data d => d -> m d)
-> QueryArg ftype -> m (QueryArg ftype)
forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> QueryArg ftype -> m (QueryArg ftype)
forall ftype (c :: * -> *).
Data ftype =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (QueryArg ftype)
forall ftype (c :: * -> *).
Data ftype =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QueryArg ftype -> c (QueryArg ftype)
forall ftype (t :: * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (QueryArg ftype))
forall ftype (t :: * -> * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (QueryArg ftype))
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) -> QueryArg ftype -> u
forall u. (forall d. Data d => d -> u) -> QueryArg ftype -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QueryArg ftype -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QueryArg ftype -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> QueryArg ftype -> m (QueryArg ftype)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> QueryArg ftype -> m (QueryArg ftype)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (QueryArg ftype)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QueryArg ftype -> c (QueryArg ftype)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (QueryArg ftype))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (QueryArg ftype))
$cgfoldl :: forall ftype (c :: * -> *).
Data ftype =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QueryArg ftype -> c (QueryArg ftype)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QueryArg ftype -> c (QueryArg ftype)
$cgunfold :: forall ftype (c :: * -> *).
Data ftype =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (QueryArg ftype)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (QueryArg ftype)
$ctoConstr :: forall ftype. Data ftype => QueryArg ftype -> Constr
toConstr :: QueryArg ftype -> Constr
$cdataTypeOf :: forall ftype. Data ftype => QueryArg ftype -> DataType
dataTypeOf :: QueryArg ftype -> DataType
$cdataCast1 :: forall ftype (t :: * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (QueryArg ftype))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (QueryArg ftype))
$cdataCast2 :: forall ftype (t :: * -> * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (QueryArg ftype))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (QueryArg ftype))
$cgmapT :: forall ftype.
Data ftype =>
(forall b. Data b => b -> b) -> QueryArg ftype -> QueryArg ftype
gmapT :: (forall b. Data b => b -> b) -> QueryArg ftype -> QueryArg ftype
$cgmapQl :: forall ftype r r'.
Data ftype =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QueryArg ftype -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QueryArg ftype -> r
$cgmapQr :: forall ftype r r'.
Data ftype =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QueryArg ftype -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QueryArg ftype -> r
$cgmapQ :: forall ftype u.
Data ftype =>
(forall d. Data d => d -> u) -> QueryArg ftype -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> QueryArg ftype -> [u]
$cgmapQi :: forall ftype u.
Data ftype =>
Int -> (forall d. Data d => d -> u) -> QueryArg ftype -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> QueryArg ftype -> u
$cgmapM :: forall ftype (m :: * -> *).
(Data ftype, Monad m) =>
(forall d. Data d => d -> m d)
-> QueryArg ftype -> m (QueryArg ftype)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> QueryArg ftype -> m (QueryArg ftype)
$cgmapMp :: forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> QueryArg ftype -> m (QueryArg ftype)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> QueryArg ftype -> m (QueryArg ftype)
$cgmapMo :: forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> QueryArg ftype -> m (QueryArg ftype)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> QueryArg ftype -> m (QueryArg ftype)
Data, QueryArg ftype -> QueryArg ftype -> Bool
(QueryArg ftype -> QueryArg ftype -> Bool)
-> (QueryArg ftype -> QueryArg ftype -> Bool)
-> Eq (QueryArg ftype)
forall ftype. Eq ftype => QueryArg ftype -> QueryArg ftype -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall ftype. Eq ftype => QueryArg ftype -> QueryArg ftype -> Bool
== :: QueryArg ftype -> QueryArg ftype -> Bool
$c/= :: forall ftype. Eq ftype => QueryArg ftype -> QueryArg ftype -> Bool
/= :: QueryArg ftype -> QueryArg ftype -> Bool
Eq, Int -> QueryArg ftype -> ShowS
[QueryArg ftype] -> ShowS
QueryArg ftype -> String
(Int -> QueryArg ftype -> ShowS)
-> (QueryArg ftype -> String)
-> ([QueryArg ftype] -> ShowS)
-> Show (QueryArg ftype)
forall ftype. Show ftype => Int -> QueryArg ftype -> ShowS
forall ftype. Show ftype => [QueryArg ftype] -> ShowS
forall ftype. Show ftype => QueryArg ftype -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall ftype. Show ftype => Int -> QueryArg ftype -> ShowS
showsPrec :: Int -> QueryArg ftype -> ShowS
$cshow :: forall ftype. Show ftype => QueryArg ftype -> String
show :: QueryArg ftype -> String
$cshowList :: forall ftype. Show ftype => [QueryArg ftype] -> ShowS
showList :: [QueryArg ftype] -> ShowS
Show, Typeable)
makeLenses ''QueryArg
data ftype =
{ :: Arg ftype }
|
{ :: Arg ftype
, :: Text
}
deriving (Typeable (HeaderArg ftype)
Typeable (HeaderArg ftype) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HeaderArg ftype -> c (HeaderArg ftype))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (HeaderArg ftype))
-> (HeaderArg ftype -> Constr)
-> (HeaderArg ftype -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (HeaderArg ftype)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (HeaderArg ftype)))
-> ((forall b. Data b => b -> b)
-> HeaderArg ftype -> HeaderArg ftype)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HeaderArg ftype -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HeaderArg ftype -> r)
-> (forall u.
(forall d. Data d => d -> u) -> HeaderArg ftype -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> HeaderArg ftype -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HeaderArg ftype -> m (HeaderArg ftype))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HeaderArg ftype -> m (HeaderArg ftype))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HeaderArg ftype -> m (HeaderArg ftype))
-> Data (HeaderArg ftype)
HeaderArg ftype -> Constr
HeaderArg ftype -> DataType
(forall b. Data b => b -> b) -> HeaderArg ftype -> HeaderArg ftype
forall ftype. Data ftype => Typeable (HeaderArg ftype)
forall ftype. Data ftype => HeaderArg ftype -> Constr
forall ftype. Data ftype => HeaderArg ftype -> DataType
forall ftype.
Data ftype =>
(forall b. Data b => b -> b) -> HeaderArg ftype -> HeaderArg ftype
forall ftype u.
Data ftype =>
Int -> (forall d. Data d => d -> u) -> HeaderArg ftype -> u
forall ftype u.
Data ftype =>
(forall d. Data d => d -> u) -> HeaderArg ftype -> [u]
forall ftype r r'.
Data ftype =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HeaderArg ftype -> r
forall ftype r r'.
Data ftype =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HeaderArg ftype -> r
forall ftype (m :: * -> *).
(Data ftype, Monad m) =>
(forall d. Data d => d -> m d)
-> HeaderArg ftype -> m (HeaderArg ftype)
forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> HeaderArg ftype -> m (HeaderArg ftype)
forall ftype (c :: * -> *).
Data ftype =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (HeaderArg ftype)
forall ftype (c :: * -> *).
Data ftype =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HeaderArg ftype -> c (HeaderArg ftype)
forall ftype (t :: * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (HeaderArg ftype))
forall ftype (t :: * -> * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (HeaderArg ftype))
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) -> HeaderArg ftype -> u
forall u. (forall d. Data d => d -> u) -> HeaderArg ftype -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HeaderArg ftype -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HeaderArg ftype -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HeaderArg ftype -> m (HeaderArg ftype)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HeaderArg ftype -> m (HeaderArg ftype)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (HeaderArg ftype)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HeaderArg ftype -> c (HeaderArg ftype)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (HeaderArg ftype))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (HeaderArg ftype))
$cgfoldl :: forall ftype (c :: * -> *).
Data ftype =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HeaderArg ftype -> c (HeaderArg ftype)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HeaderArg ftype -> c (HeaderArg ftype)
$cgunfold :: forall ftype (c :: * -> *).
Data ftype =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (HeaderArg ftype)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (HeaderArg ftype)
$ctoConstr :: forall ftype. Data ftype => HeaderArg ftype -> Constr
toConstr :: HeaderArg ftype -> Constr
$cdataTypeOf :: forall ftype. Data ftype => HeaderArg ftype -> DataType
dataTypeOf :: HeaderArg ftype -> DataType
$cdataCast1 :: forall ftype (t :: * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (HeaderArg ftype))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (HeaderArg ftype))
$cdataCast2 :: forall ftype (t :: * -> * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (HeaderArg ftype))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (HeaderArg ftype))
$cgmapT :: forall ftype.
Data ftype =>
(forall b. Data b => b -> b) -> HeaderArg ftype -> HeaderArg ftype
gmapT :: (forall b. Data b => b -> b) -> HeaderArg ftype -> HeaderArg ftype
$cgmapQl :: forall ftype r r'.
Data ftype =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HeaderArg ftype -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HeaderArg ftype -> r
$cgmapQr :: forall ftype r r'.
Data ftype =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HeaderArg ftype -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HeaderArg ftype -> r
$cgmapQ :: forall ftype u.
Data ftype =>
(forall d. Data d => d -> u) -> HeaderArg ftype -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> HeaderArg ftype -> [u]
$cgmapQi :: forall ftype u.
Data ftype =>
Int -> (forall d. Data d => d -> u) -> HeaderArg ftype -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> HeaderArg ftype -> u
$cgmapM :: forall ftype (m :: * -> *).
(Data ftype, Monad m) =>
(forall d. Data d => d -> m d)
-> HeaderArg ftype -> m (HeaderArg ftype)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HeaderArg ftype -> m (HeaderArg ftype)
$cgmapMp :: forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> HeaderArg ftype -> m (HeaderArg ftype)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HeaderArg ftype -> m (HeaderArg ftype)
$cgmapMo :: forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> HeaderArg ftype -> m (HeaderArg ftype)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HeaderArg ftype -> m (HeaderArg ftype)
Data, HeaderArg ftype -> HeaderArg ftype -> Bool
(HeaderArg ftype -> HeaderArg ftype -> Bool)
-> (HeaderArg ftype -> HeaderArg ftype -> Bool)
-> Eq (HeaderArg ftype)
forall ftype.
Eq ftype =>
HeaderArg ftype -> HeaderArg ftype -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall ftype.
Eq ftype =>
HeaderArg ftype -> HeaderArg ftype -> Bool
== :: HeaderArg ftype -> HeaderArg ftype -> Bool
$c/= :: forall ftype.
Eq ftype =>
HeaderArg ftype -> HeaderArg ftype -> Bool
/= :: HeaderArg ftype -> HeaderArg ftype -> Bool
Eq, Int -> HeaderArg ftype -> ShowS
[HeaderArg ftype] -> ShowS
HeaderArg ftype -> String
(Int -> HeaderArg ftype -> ShowS)
-> (HeaderArg ftype -> String)
-> ([HeaderArg ftype] -> ShowS)
-> Show (HeaderArg ftype)
forall ftype. Show ftype => Int -> HeaderArg ftype -> ShowS
forall ftype. Show ftype => [HeaderArg ftype] -> ShowS
forall ftype. Show ftype => HeaderArg ftype -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall ftype. Show ftype => Int -> HeaderArg ftype -> ShowS
showsPrec :: Int -> HeaderArg ftype -> ShowS
$cshow :: forall ftype. Show ftype => HeaderArg ftype -> String
show :: HeaderArg ftype -> String
$cshowList :: forall ftype. Show ftype => [HeaderArg ftype] -> ShowS
showList :: [HeaderArg ftype] -> ShowS
Show, Typeable)
data Url ftype = Url
{ forall ftype. Url ftype -> Path ftype
_path :: Path ftype
, forall ftype. Url ftype -> [QueryArg ftype]
_queryStr :: [QueryArg ftype]
, forall ftype. Url ftype -> Maybe ftype
_frag :: Maybe ftype
}
deriving (Typeable (Url ftype)
Typeable (Url ftype) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Url ftype -> c (Url ftype))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Url ftype))
-> (Url ftype -> Constr)
-> (Url ftype -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Url ftype)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Url ftype)))
-> ((forall b. Data b => b -> b) -> Url ftype -> Url ftype)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Url ftype -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Url ftype -> r)
-> (forall u. (forall d. Data d => d -> u) -> Url ftype -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Url ftype -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Url ftype -> m (Url ftype))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Url ftype -> m (Url ftype))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Url ftype -> m (Url ftype))
-> Data (Url ftype)
Url ftype -> Constr
Url ftype -> DataType
(forall b. Data b => b -> b) -> Url ftype -> Url ftype
forall ftype. Data ftype => Typeable (Url ftype)
forall ftype. Data ftype => Url ftype -> Constr
forall ftype. Data ftype => Url ftype -> DataType
forall ftype.
Data ftype =>
(forall b. Data b => b -> b) -> Url ftype -> Url ftype
forall ftype u.
Data ftype =>
Int -> (forall d. Data d => d -> u) -> Url ftype -> u
forall ftype u.
Data ftype =>
(forall d. Data d => d -> u) -> Url ftype -> [u]
forall ftype r r'.
Data ftype =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Url ftype -> r
forall ftype r r'.
Data ftype =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Url ftype -> r
forall ftype (m :: * -> *).
(Data ftype, Monad m) =>
(forall d. Data d => d -> m d) -> Url ftype -> m (Url ftype)
forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Url ftype -> m (Url ftype)
forall ftype (c :: * -> *).
Data ftype =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Url ftype)
forall ftype (c :: * -> *).
Data ftype =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Url ftype -> c (Url ftype)
forall ftype (t :: * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Url ftype))
forall ftype (t :: * -> * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Url ftype))
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) -> Url ftype -> u
forall u. (forall d. Data d => d -> u) -> Url ftype -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Url ftype -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Url ftype -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Url ftype -> m (Url ftype)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Url ftype -> m (Url ftype)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Url ftype)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Url ftype -> c (Url ftype)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Url ftype))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Url ftype))
$cgfoldl :: forall ftype (c :: * -> *).
Data ftype =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Url ftype -> c (Url ftype)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Url ftype -> c (Url ftype)
$cgunfold :: forall ftype (c :: * -> *).
Data ftype =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Url ftype)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Url ftype)
$ctoConstr :: forall ftype. Data ftype => Url ftype -> Constr
toConstr :: Url ftype -> Constr
$cdataTypeOf :: forall ftype. Data ftype => Url ftype -> DataType
dataTypeOf :: Url ftype -> DataType
$cdataCast1 :: forall ftype (t :: * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Url ftype))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Url ftype))
$cdataCast2 :: forall ftype (t :: * -> * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Url ftype))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Url ftype))
$cgmapT :: forall ftype.
Data ftype =>
(forall b. Data b => b -> b) -> Url ftype -> Url ftype
gmapT :: (forall b. Data b => b -> b) -> Url ftype -> Url ftype
$cgmapQl :: forall ftype r r'.
Data ftype =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Url ftype -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Url ftype -> r
$cgmapQr :: forall ftype r r'.
Data ftype =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Url ftype -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Url ftype -> r
$cgmapQ :: forall ftype u.
Data ftype =>
(forall d. Data d => d -> u) -> Url ftype -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Url ftype -> [u]
$cgmapQi :: forall ftype u.
Data ftype =>
Int -> (forall d. Data d => d -> u) -> Url ftype -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Url ftype -> u
$cgmapM :: forall ftype (m :: * -> *).
(Data ftype, Monad m) =>
(forall d. Data d => d -> m d) -> Url ftype -> m (Url ftype)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Url ftype -> m (Url ftype)
$cgmapMp :: forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Url ftype -> m (Url ftype)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Url ftype -> m (Url ftype)
$cgmapMo :: forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Url ftype -> m (Url ftype)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Url ftype -> m (Url ftype)
Data, Url ftype -> Url ftype -> Bool
(Url ftype -> Url ftype -> Bool)
-> (Url ftype -> Url ftype -> Bool) -> Eq (Url ftype)
forall ftype. Eq ftype => Url ftype -> Url ftype -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall ftype. Eq ftype => Url ftype -> Url ftype -> Bool
== :: Url ftype -> Url ftype -> Bool
$c/= :: forall ftype. Eq ftype => Url ftype -> Url ftype -> Bool
/= :: Url ftype -> Url ftype -> Bool
Eq, Int -> Url ftype -> ShowS
[Url ftype] -> ShowS
Url ftype -> String
(Int -> Url ftype -> ShowS)
-> (Url ftype -> String)
-> ([Url ftype] -> ShowS)
-> Show (Url ftype)
forall ftype. Show ftype => Int -> Url ftype -> ShowS
forall ftype. Show ftype => [Url ftype] -> ShowS
forall ftype. Show ftype => Url ftype -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall ftype. Show ftype => Int -> Url ftype -> ShowS
showsPrec :: Int -> Url ftype -> ShowS
$cshow :: forall ftype. Show ftype => Url ftype -> String
show :: Url ftype -> String
$cshowList :: forall ftype. Show ftype => [Url ftype] -> ShowS
showList :: [Url ftype] -> ShowS
Show, Typeable)
defUrl :: Url ftype
defUrl :: forall ftype. Url ftype
defUrl = Path ftype -> [QueryArg ftype] -> Maybe ftype -> Url ftype
forall ftype.
Path ftype -> [QueryArg ftype] -> Maybe ftype -> Url ftype
Url [] [] Maybe ftype
forall a. Maybe a
Nothing
makeLenses ''Url
data ReqBodyContentType = ReqBodyJSON | ReqBodyMultipart
deriving (Typeable ReqBodyContentType
Typeable ReqBodyContentType =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ReqBodyContentType
-> c ReqBodyContentType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReqBodyContentType)
-> (ReqBodyContentType -> Constr)
-> (ReqBodyContentType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReqBodyContentType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReqBodyContentType))
-> ((forall b. Data b => b -> b)
-> ReqBodyContentType -> ReqBodyContentType)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReqBodyContentType -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReqBodyContentType -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ReqBodyContentType -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ReqBodyContentType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ReqBodyContentType -> m ReqBodyContentType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReqBodyContentType -> m ReqBodyContentType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReqBodyContentType -> m ReqBodyContentType)
-> Data ReqBodyContentType
ReqBodyContentType -> Constr
ReqBodyContentType -> DataType
(forall b. Data b => b -> b)
-> ReqBodyContentType -> ReqBodyContentType
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) -> ReqBodyContentType -> u
forall u. (forall d. Data d => d -> u) -> ReqBodyContentType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReqBodyContentType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReqBodyContentType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ReqBodyContentType -> m ReqBodyContentType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReqBodyContentType -> m ReqBodyContentType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReqBodyContentType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ReqBodyContentType
-> c ReqBodyContentType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReqBodyContentType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReqBodyContentType)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ReqBodyContentType
-> c ReqBodyContentType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ReqBodyContentType
-> c ReqBodyContentType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReqBodyContentType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReqBodyContentType
$ctoConstr :: ReqBodyContentType -> Constr
toConstr :: ReqBodyContentType -> Constr
$cdataTypeOf :: ReqBodyContentType -> DataType
dataTypeOf :: ReqBodyContentType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReqBodyContentType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReqBodyContentType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReqBodyContentType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReqBodyContentType)
$cgmapT :: (forall b. Data b => b -> b)
-> ReqBodyContentType -> ReqBodyContentType
gmapT :: (forall b. Data b => b -> b)
-> ReqBodyContentType -> ReqBodyContentType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReqBodyContentType -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReqBodyContentType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReqBodyContentType -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReqBodyContentType -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ReqBodyContentType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ReqBodyContentType -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ReqBodyContentType -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ReqBodyContentType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ReqBodyContentType -> m ReqBodyContentType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ReqBodyContentType -> m ReqBodyContentType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReqBodyContentType -> m ReqBodyContentType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReqBodyContentType -> m ReqBodyContentType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReqBodyContentType -> m ReqBodyContentType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReqBodyContentType -> m ReqBodyContentType
Data, ReqBodyContentType -> ReqBodyContentType -> Bool
(ReqBodyContentType -> ReqBodyContentType -> Bool)
-> (ReqBodyContentType -> ReqBodyContentType -> Bool)
-> Eq ReqBodyContentType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReqBodyContentType -> ReqBodyContentType -> Bool
== :: ReqBodyContentType -> ReqBodyContentType -> Bool
$c/= :: ReqBodyContentType -> ReqBodyContentType -> Bool
/= :: ReqBodyContentType -> ReqBodyContentType -> Bool
Eq, Int -> ReqBodyContentType -> ShowS
[ReqBodyContentType] -> ShowS
ReqBodyContentType -> String
(Int -> ReqBodyContentType -> ShowS)
-> (ReqBodyContentType -> String)
-> ([ReqBodyContentType] -> ShowS)
-> Show ReqBodyContentType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReqBodyContentType -> ShowS
showsPrec :: Int -> ReqBodyContentType -> ShowS
$cshow :: ReqBodyContentType -> String
show :: ReqBodyContentType -> String
$cshowList :: [ReqBodyContentType] -> ShowS
showList :: [ReqBodyContentType] -> ShowS
Show, ReadPrec [ReqBodyContentType]
ReadPrec ReqBodyContentType
Int -> ReadS ReqBodyContentType
ReadS [ReqBodyContentType]
(Int -> ReadS ReqBodyContentType)
-> ReadS [ReqBodyContentType]
-> ReadPrec ReqBodyContentType
-> ReadPrec [ReqBodyContentType]
-> Read ReqBodyContentType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ReqBodyContentType
readsPrec :: Int -> ReadS ReqBodyContentType
$creadList :: ReadS [ReqBodyContentType]
readList :: ReadS [ReqBodyContentType]
$creadPrec :: ReadPrec ReqBodyContentType
readPrec :: ReadPrec ReqBodyContentType
$creadListPrec :: ReadPrec [ReqBodyContentType]
readListPrec :: ReadPrec [ReqBodyContentType]
Read)
data Req ftype = Req
{ forall ftype. Req ftype -> Url ftype
_reqUrl :: Url ftype
, forall ftype. Req ftype -> Method
_reqMethod :: HTTP.Method
, :: [HeaderArg ftype]
, forall ftype. Req ftype -> Maybe ftype
_reqBody :: Maybe ftype
, forall ftype. Req ftype -> Maybe ftype
_reqReturnType :: Maybe ftype
, forall ftype. Req ftype -> FunctionName
_reqFuncName :: FunctionName
, forall ftype. Req ftype -> ReqBodyContentType
_reqBodyContentType :: ReqBodyContentType
}
deriving (Typeable (Req ftype)
Typeable (Req ftype) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Req ftype -> c (Req ftype))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Req ftype))
-> (Req ftype -> Constr)
-> (Req ftype -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Req ftype)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Req ftype)))
-> ((forall b. Data b => b -> b) -> Req ftype -> Req ftype)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Req ftype -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Req ftype -> r)
-> (forall u. (forall d. Data d => d -> u) -> Req ftype -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Req ftype -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Req ftype -> m (Req ftype))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Req ftype -> m (Req ftype))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Req ftype -> m (Req ftype))
-> Data (Req ftype)
Req ftype -> Constr
Req ftype -> DataType
(forall b. Data b => b -> b) -> Req ftype -> Req ftype
forall ftype. Data ftype => Typeable (Req ftype)
forall ftype. Data ftype => Req ftype -> Constr
forall ftype. Data ftype => Req ftype -> DataType
forall ftype.
Data ftype =>
(forall b. Data b => b -> b) -> Req ftype -> Req ftype
forall ftype u.
Data ftype =>
Int -> (forall d. Data d => d -> u) -> Req ftype -> u
forall ftype u.
Data ftype =>
(forall d. Data d => d -> u) -> Req ftype -> [u]
forall ftype r r'.
Data ftype =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Req ftype -> r
forall ftype r r'.
Data ftype =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Req ftype -> r
forall ftype (m :: * -> *).
(Data ftype, Monad m) =>
(forall d. Data d => d -> m d) -> Req ftype -> m (Req ftype)
forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Req ftype -> m (Req ftype)
forall ftype (c :: * -> *).
Data ftype =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Req ftype)
forall ftype (c :: * -> *).
Data ftype =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Req ftype -> c (Req ftype)
forall ftype (t :: * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Req ftype))
forall ftype (t :: * -> * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Req ftype))
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) -> Req ftype -> u
forall u. (forall d. Data d => d -> u) -> Req ftype -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Req ftype -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Req ftype -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Req ftype -> m (Req ftype)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Req ftype -> m (Req ftype)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Req ftype)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Req ftype -> c (Req ftype)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Req ftype))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Req ftype))
$cgfoldl :: forall ftype (c :: * -> *).
Data ftype =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Req ftype -> c (Req ftype)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Req ftype -> c (Req ftype)
$cgunfold :: forall ftype (c :: * -> *).
Data ftype =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Req ftype)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Req ftype)
$ctoConstr :: forall ftype. Data ftype => Req ftype -> Constr
toConstr :: Req ftype -> Constr
$cdataTypeOf :: forall ftype. Data ftype => Req ftype -> DataType
dataTypeOf :: Req ftype -> DataType
$cdataCast1 :: forall ftype (t :: * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Req ftype))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Req ftype))
$cdataCast2 :: forall ftype (t :: * -> * -> *) (c :: * -> *).
(Data ftype, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Req ftype))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Req ftype))
$cgmapT :: forall ftype.
Data ftype =>
(forall b. Data b => b -> b) -> Req ftype -> Req ftype
gmapT :: (forall b. Data b => b -> b) -> Req ftype -> Req ftype
$cgmapQl :: forall ftype r r'.
Data ftype =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Req ftype -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Req ftype -> r
$cgmapQr :: forall ftype r r'.
Data ftype =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Req ftype -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Req ftype -> r
$cgmapQ :: forall ftype u.
Data ftype =>
(forall d. Data d => d -> u) -> Req ftype -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Req ftype -> [u]
$cgmapQi :: forall ftype u.
Data ftype =>
Int -> (forall d. Data d => d -> u) -> Req ftype -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Req ftype -> u
$cgmapM :: forall ftype (m :: * -> *).
(Data ftype, Monad m) =>
(forall d. Data d => d -> m d) -> Req ftype -> m (Req ftype)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Req ftype -> m (Req ftype)
$cgmapMp :: forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Req ftype -> m (Req ftype)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Req ftype -> m (Req ftype)
$cgmapMo :: forall ftype (m :: * -> *).
(Data ftype, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Req ftype -> m (Req ftype)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Req ftype -> m (Req ftype)
Data, Req ftype -> Req ftype -> Bool
(Req ftype -> Req ftype -> Bool)
-> (Req ftype -> Req ftype -> Bool) -> Eq (Req ftype)
forall ftype. Eq ftype => Req ftype -> Req ftype -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall ftype. Eq ftype => Req ftype -> Req ftype -> Bool
== :: Req ftype -> Req ftype -> Bool
$c/= :: forall ftype. Eq ftype => Req ftype -> Req ftype -> Bool
/= :: Req ftype -> Req ftype -> Bool
Eq, Int -> Req ftype -> ShowS
[Req ftype] -> ShowS
Req ftype -> String
(Int -> Req ftype -> ShowS)
-> (Req ftype -> String)
-> ([Req ftype] -> ShowS)
-> Show (Req ftype)
forall ftype. Show ftype => Int -> Req ftype -> ShowS
forall ftype. Show ftype => [Req ftype] -> ShowS
forall ftype. Show ftype => Req ftype -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall ftype. Show ftype => Int -> Req ftype -> ShowS
showsPrec :: Int -> Req ftype -> ShowS
$cshow :: forall ftype. Show ftype => Req ftype -> String
show :: Req ftype -> String
$cshowList :: forall ftype. Show ftype => [Req ftype] -> ShowS
showList :: [Req ftype] -> ShowS
Show, Typeable)
defReq :: Req ftype
defReq :: forall ftype. Req ftype
defReq = Url ftype
-> Method
-> [HeaderArg ftype]
-> Maybe ftype
-> Maybe ftype
-> FunctionName
-> ReqBodyContentType
-> Req ftype
forall ftype.
Url ftype
-> Method
-> [HeaderArg ftype]
-> Maybe ftype
-> Maybe ftype
-> FunctionName
-> ReqBodyContentType
-> Req ftype
Req Url ftype
forall ftype. Url ftype
defUrl Method
"GET" [] Maybe ftype
forall a. Maybe a
Nothing Maybe ftype
forall a. Maybe a
Nothing ([Text] -> FunctionName
FunctionName []) ReqBodyContentType
ReqBodyJSON
class HasForeignType lang ftype a where
typeFor :: Proxy lang -> Proxy ftype -> Proxy a -> ftype
data NoTypes
instance HasForeignType NoTypes NoContent a where
typeFor :: Proxy NoTypes -> Proxy NoContent -> Proxy a -> NoContent
typeFor Proxy NoTypes
_ Proxy NoContent
_ Proxy a
_ = NoContent
NoContent
class HasForeign lang ftype (api :: *) where
type Foreign ftype api :: *
foreignFor :: Proxy lang -> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
instance (HasForeign lang ftype a, HasForeign lang ftype b)
=> HasForeign lang ftype (a :<|> b) where
type Foreign ftype (a :<|> b) = Foreign ftype a :<|> Foreign ftype b
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (a :<|> b)
-> Req ftype
-> Foreign ftype (a :<|> b)
foreignFor Proxy lang
lang Proxy ftype
ftype Proxy (a :<|> b)
Proxy Req ftype
req =
Proxy lang
-> Proxy ftype -> Proxy a -> Req ftype -> Foreign ftype a
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
ftype (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a) Req ftype
req
Foreign ftype a
-> Foreign ftype b -> Foreign ftype a :<|> Foreign ftype b
forall a b. a -> b -> a :<|> b
:<|> Proxy lang
-> Proxy ftype -> Proxy b -> Req ftype -> Foreign ftype b
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
ftype (Proxy b
forall {k} (t :: k). Proxy t
Proxy :: Proxy b) Req ftype
req
data EmptyForeignAPI = EmptyForeignAPI
instance HasForeign lang ftype EmptyAPI where
type Foreign ftype EmptyAPI = EmptyForeignAPI
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy EmptyAPI
-> Req ftype
-> Foreign ftype EmptyAPI
foreignFor Proxy lang
Proxy Proxy ftype
Proxy Proxy EmptyAPI
Proxy Req ftype
_ = EmptyForeignAPI
Foreign ftype EmptyAPI
EmptyForeignAPI
instance (KnownSymbol sym, HasForeignType lang ftype t, HasForeign lang ftype api)
=> HasForeign lang ftype (Capture' mods sym t :> api) where
type Foreign ftype (Capture' mods sym t :> api) = Foreign ftype api
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (Capture' mods sym t :> api)
-> Req ftype
-> Foreign ftype (Capture' mods sym t :> api)
foreignFor Proxy lang
lang Proxy ftype
Proxy Proxy (Capture' mods sym t :> api)
Proxy Req ftype
req =
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
forall {k} (t :: k). Proxy t
Proxy (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) (Req ftype -> Foreign ftype api) -> Req ftype -> Foreign ftype api
forall a b. (a -> b) -> a -> b
$
Req ftype
req Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (Url ftype -> Identity (Url ftype))
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(Url ftype -> f (Url ftype)) -> Req ftype -> f (Req ftype)
reqUrl ((Url ftype -> Identity (Url ftype))
-> Req ftype -> Identity (Req ftype))
-> ((Path ftype -> Identity (Path ftype))
-> Url ftype -> Identity (Url ftype))
-> (Path ftype -> Identity (Path ftype))
-> Req ftype
-> Identity (Req ftype)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Path ftype -> Identity (Path ftype))
-> Url ftype -> Identity (Url ftype)
forall ftype (f :: * -> *).
Functor f =>
(Path ftype -> f (Path ftype)) -> Url ftype -> f (Url ftype)
path ((Path ftype -> Identity (Path ftype))
-> Req ftype -> Identity (Req ftype))
-> Path ftype -> Req ftype -> Req ftype
forall a s t. Semigroup a => ASetter s t a a -> a -> s -> t
<>~ [SegmentType ftype -> Segment ftype
forall ftype. SegmentType ftype -> Segment ftype
Segment (Arg ftype -> SegmentType ftype
forall ftype. Arg ftype -> SegmentType ftype
Cap Arg ftype
arg)]
Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (FunctionName -> Identity FunctionName)
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(FunctionName -> f FunctionName) -> Req ftype -> f (Req ftype)
reqFuncName ((FunctionName -> Identity FunctionName)
-> Req ftype -> Identity (Req ftype))
-> (([Text] -> Identity [Text])
-> FunctionName -> Identity FunctionName)
-> ([Text] -> Identity [Text])
-> Req ftype
-> Identity (Req ftype)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Text] -> Identity [Text])
-> FunctionName -> Identity FunctionName
Iso' FunctionName [Text]
_FunctionName (([Text] -> Identity [Text]) -> Req ftype -> Identity (Req ftype))
-> ([Text] -> [Text]) -> Req ftype -> Req ftype
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ([Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
"by", Text
str])
where
str :: Text
str = String -> Text
pack (String -> Text) -> (Proxy sym -> String) -> Proxy sym -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy sym -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy sym -> Text) -> Proxy sym -> Text
forall a b. (a -> b) -> a -> b
$ (Proxy sym
forall {k} (t :: k). Proxy t
Proxy :: Proxy sym)
ftype :: ftype
ftype = Proxy lang -> Proxy ftype -> Proxy t -> ftype
forall {k} {k} (lang :: k) ftype (a :: k).
HasForeignType lang ftype a =>
Proxy lang -> Proxy ftype -> Proxy a -> ftype
typeFor Proxy lang
lang (Proxy ftype
forall {k} (t :: k). Proxy t
Proxy :: Proxy ftype) (Proxy t
forall {k} (t :: k). Proxy t
Proxy :: Proxy t)
arg :: Arg ftype
arg = Arg
{ _argName :: PathSegment
_argName = Text -> PathSegment
PathSegment Text
str
, _argType :: ftype
_argType = ftype
ftype }
instance (KnownSymbol sym, HasForeignType lang ftype [t], HasForeign lang ftype sublayout)
=> HasForeign lang ftype (CaptureAll sym t :> sublayout) where
type Foreign ftype (CaptureAll sym t :> sublayout) = Foreign ftype sublayout
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (CaptureAll sym t :> sublayout)
-> Req ftype
-> Foreign ftype (CaptureAll sym t :> sublayout)
foreignFor Proxy lang
lang Proxy ftype
Proxy Proxy (CaptureAll sym t :> sublayout)
Proxy Req ftype
req =
Proxy lang
-> Proxy ftype
-> Proxy sublayout
-> Req ftype
-> Foreign ftype sublayout
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
forall {k} (t :: k). Proxy t
Proxy (Proxy sublayout
forall {k} (t :: k). Proxy t
Proxy :: Proxy sublayout) (Req ftype -> Foreign ftype sublayout)
-> Req ftype -> Foreign ftype sublayout
forall a b. (a -> b) -> a -> b
$
Req ftype
req Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (Url ftype -> Identity (Url ftype))
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(Url ftype -> f (Url ftype)) -> Req ftype -> f (Req ftype)
reqUrl ((Url ftype -> Identity (Url ftype))
-> Req ftype -> Identity (Req ftype))
-> ((Path ftype -> Identity (Path ftype))
-> Url ftype -> Identity (Url ftype))
-> (Path ftype -> Identity (Path ftype))
-> Req ftype
-> Identity (Req ftype)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Path ftype -> Identity (Path ftype))
-> Url ftype -> Identity (Url ftype)
forall ftype (f :: * -> *).
Functor f =>
(Path ftype -> f (Path ftype)) -> Url ftype -> f (Url ftype)
path ((Path ftype -> Identity (Path ftype))
-> Req ftype -> Identity (Req ftype))
-> Path ftype -> Req ftype -> Req ftype
forall a s t. Semigroup a => ASetter s t a a -> a -> s -> t
<>~ [SegmentType ftype -> Segment ftype
forall ftype. SegmentType ftype -> Segment ftype
Segment (Arg ftype -> SegmentType ftype
forall ftype. Arg ftype -> SegmentType ftype
Cap Arg ftype
arg)]
Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (FunctionName -> Identity FunctionName)
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(FunctionName -> f FunctionName) -> Req ftype -> f (Req ftype)
reqFuncName ((FunctionName -> Identity FunctionName)
-> Req ftype -> Identity (Req ftype))
-> (([Text] -> Identity [Text])
-> FunctionName -> Identity FunctionName)
-> ([Text] -> Identity [Text])
-> Req ftype
-> Identity (Req ftype)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Text] -> Identity [Text])
-> FunctionName -> Identity FunctionName
Iso' FunctionName [Text]
_FunctionName (([Text] -> Identity [Text]) -> Req ftype -> Identity (Req ftype))
-> ([Text] -> [Text]) -> Req ftype -> Req ftype
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ([Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
"by", Text
str])
where
str :: Text
str = String -> Text
pack (String -> Text) -> (Proxy sym -> String) -> Proxy sym -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy sym -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy sym -> Text) -> Proxy sym -> Text
forall a b. (a -> b) -> a -> b
$ (Proxy sym
forall {k} (t :: k). Proxy t
Proxy :: Proxy sym)
ftype :: ftype
ftype = Proxy lang -> Proxy ftype -> Proxy [t] -> ftype
forall {k} {k} (lang :: k) ftype (a :: k).
HasForeignType lang ftype a =>
Proxy lang -> Proxy ftype -> Proxy a -> ftype
typeFor Proxy lang
lang (Proxy ftype
forall {k} (t :: k). Proxy t
Proxy :: Proxy ftype) (Proxy [t]
forall {k} (t :: k). Proxy t
Proxy :: Proxy [t])
arg :: Arg ftype
arg = Arg
{ _argName :: PathSegment
_argName = Text -> PathSegment
PathSegment Text
str
, _argType :: ftype
_argType = ftype
ftype }
instance (Elem JSON list, HasForeignType lang ftype a, ReflectMethod method)
=> HasForeign lang ftype (Verb method status list a) where
type Foreign ftype (Verb method status list a) = Req ftype
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (Verb method status list a)
-> Req ftype
-> Foreign ftype (Verb method status list a)
foreignFor Proxy lang
lang Proxy ftype
Proxy Proxy (Verb method status list a)
Proxy Req ftype
req =
Req ftype
req Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (FunctionName -> Identity FunctionName)
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(FunctionName -> f FunctionName) -> Req ftype -> f (Req ftype)
reqFuncName ((FunctionName -> Identity FunctionName)
-> Req ftype -> Identity (Req ftype))
-> (([Text] -> Identity [Text])
-> FunctionName -> Identity FunctionName)
-> ([Text] -> Identity [Text])
-> Req ftype
-> Identity (Req ftype)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Text] -> Identity [Text])
-> FunctionName -> Identity FunctionName
Iso' FunctionName [Text]
_FunctionName (([Text] -> Identity [Text]) -> Req ftype -> Identity (Req ftype))
-> ([Text] -> [Text]) -> Req ftype -> Req ftype
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (Text
methodLC Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:)
Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (Method -> Identity Method) -> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(Method -> f Method) -> Req ftype -> f (Req ftype)
reqMethod ((Method -> Identity Method) -> Req ftype -> Identity (Req ftype))
-> Method -> Req ftype -> Req ftype
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Method
method
Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (Maybe ftype -> Identity (Maybe ftype))
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(Maybe ftype -> f (Maybe ftype)) -> Req ftype -> f (Req ftype)
reqReturnType ((Maybe ftype -> Identity (Maybe ftype))
-> Req ftype -> Identity (Req ftype))
-> Maybe ftype -> Req ftype -> Req ftype
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ftype -> Maybe ftype
forall a. a -> Maybe a
Just ftype
retType
where
retType :: ftype
retType = Proxy lang -> Proxy ftype -> Proxy a -> ftype
forall {k} {k} (lang :: k) ftype (a :: k).
HasForeignType lang ftype a =>
Proxy lang -> Proxy ftype -> Proxy a -> ftype
typeFor Proxy lang
lang (Proxy ftype
forall {k} (t :: k). Proxy t
Proxy :: Proxy ftype) (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a)
method :: Method
method = Proxy method -> Method
forall {k} (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod (Proxy method
forall {k} (t :: k). Proxy t
Proxy :: Proxy method)
methodLC :: Text
methodLC = Text -> Text
toLower (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Method -> Text
decodeUtf8 Method
method
instance (HasForeignType lang ftype NoContent, ReflectMethod method)
=> HasForeign lang ftype (NoContentVerb method) where
type Foreign ftype (NoContentVerb method) = Req ftype
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (NoContentVerb method)
-> Req ftype
-> Foreign ftype (NoContentVerb method)
foreignFor Proxy lang
lang Proxy ftype
Proxy Proxy (NoContentVerb method)
Proxy Req ftype
req =
Req ftype
req Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (FunctionName -> Identity FunctionName)
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(FunctionName -> f FunctionName) -> Req ftype -> f (Req ftype)
reqFuncName ((FunctionName -> Identity FunctionName)
-> Req ftype -> Identity (Req ftype))
-> (([Text] -> Identity [Text])
-> FunctionName -> Identity FunctionName)
-> ([Text] -> Identity [Text])
-> Req ftype
-> Identity (Req ftype)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Text] -> Identity [Text])
-> FunctionName -> Identity FunctionName
Iso' FunctionName [Text]
_FunctionName (([Text] -> Identity [Text]) -> Req ftype -> Identity (Req ftype))
-> ([Text] -> [Text]) -> Req ftype -> Req ftype
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (Text
methodLC Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:)
Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (Method -> Identity Method) -> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(Method -> f Method) -> Req ftype -> f (Req ftype)
reqMethod ((Method -> Identity Method) -> Req ftype -> Identity (Req ftype))
-> Method -> Req ftype -> Req ftype
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Method
method
Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (Maybe ftype -> Identity (Maybe ftype))
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(Maybe ftype -> f (Maybe ftype)) -> Req ftype -> f (Req ftype)
reqReturnType ((Maybe ftype -> Identity (Maybe ftype))
-> Req ftype -> Identity (Req ftype))
-> Maybe ftype -> Req ftype -> Req ftype
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ftype -> Maybe ftype
forall a. a -> Maybe a
Just ftype
retType
where
retType :: ftype
retType = Proxy lang -> Proxy ftype -> Proxy NoContent -> ftype
forall {k} {k} (lang :: k) ftype (a :: k).
HasForeignType lang ftype a =>
Proxy lang -> Proxy ftype -> Proxy a -> ftype
typeFor Proxy lang
lang (Proxy ftype
forall {k} (t :: k). Proxy t
Proxy :: Proxy ftype) (Proxy NoContent
forall {k} (t :: k). Proxy t
Proxy :: Proxy NoContent)
method :: Method
method = Proxy method -> Method
forall {k} (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod (Proxy method
forall {k} (t :: k). Proxy t
Proxy :: Proxy method)
methodLC :: Text
methodLC = Text -> Text
toLower (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Method -> Text
decodeUtf8 Method
method
instance (ct ~ JSON, HasForeignType lang ftype a, ReflectMethod method)
=> HasForeign lang ftype (Stream method status framing ct a) where
type Foreign ftype (Stream method status framing ct a) = Req ftype
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (Stream method status framing ct a)
-> Req ftype
-> Foreign ftype (Stream method status framing ct a)
foreignFor Proxy lang
lang Proxy ftype
Proxy Proxy (Stream method status framing ct a)
Proxy Req ftype
req =
Req ftype
req Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (FunctionName -> Identity FunctionName)
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(FunctionName -> f FunctionName) -> Req ftype -> f (Req ftype)
reqFuncName ((FunctionName -> Identity FunctionName)
-> Req ftype -> Identity (Req ftype))
-> (([Text] -> Identity [Text])
-> FunctionName -> Identity FunctionName)
-> ([Text] -> Identity [Text])
-> Req ftype
-> Identity (Req ftype)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Text] -> Identity [Text])
-> FunctionName -> Identity FunctionName
Iso' FunctionName [Text]
_FunctionName (([Text] -> Identity [Text]) -> Req ftype -> Identity (Req ftype))
-> ([Text] -> [Text]) -> Req ftype -> Req ftype
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (Text
methodLC Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:)
Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (Method -> Identity Method) -> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(Method -> f Method) -> Req ftype -> f (Req ftype)
reqMethod ((Method -> Identity Method) -> Req ftype -> Identity (Req ftype))
-> Method -> Req ftype -> Req ftype
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Method
method
Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (Maybe ftype -> Identity (Maybe ftype))
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(Maybe ftype -> f (Maybe ftype)) -> Req ftype -> f (Req ftype)
reqReturnType ((Maybe ftype -> Identity (Maybe ftype))
-> Req ftype -> Identity (Req ftype))
-> Maybe ftype -> Req ftype -> Req ftype
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ftype -> Maybe ftype
forall a. a -> Maybe a
Just ftype
retType
where
retType :: ftype
retType = Proxy lang -> Proxy ftype -> Proxy a -> ftype
forall {k} {k} (lang :: k) ftype (a :: k).
HasForeignType lang ftype a =>
Proxy lang -> Proxy ftype -> Proxy a -> ftype
typeFor Proxy lang
lang (Proxy ftype
forall {k} (t :: k). Proxy t
Proxy :: Proxy ftype) (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a)
method :: Method
method = Proxy method -> Method
forall {k} (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod (Proxy method
forall {k} (t :: k). Proxy t
Proxy :: Proxy method)
methodLC :: Text
methodLC = Text -> Text
toLower (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Method -> Text
decodeUtf8 Method
method
instance (KnownSymbol sym, HasForeignType lang ftype (RequiredArgument mods a), HasForeign lang ftype api)
=> HasForeign lang ftype (Header' mods sym a :> api) where
type Foreign ftype (Header' mods sym a :> api) = Foreign ftype api
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (Header' mods sym a :> api)
-> Req ftype
-> Foreign ftype (Header' mods sym a :> api)
foreignFor Proxy lang
lang Proxy ftype
Proxy Proxy (Header' mods sym a :> api)
Proxy Req ftype
req =
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
forall {k} (t :: k). Proxy t
Proxy Proxy api
subP (Req ftype -> Foreign ftype api) -> Req ftype -> Foreign ftype api
forall a b. (a -> b) -> a -> b
$ Req ftype
req Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& ([HeaderArg ftype] -> Identity [HeaderArg ftype])
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
([HeaderArg ftype] -> f [HeaderArg ftype])
-> Req ftype -> f (Req ftype)
reqHeaders (([HeaderArg ftype] -> Identity [HeaderArg ftype])
-> Req ftype -> Identity (Req ftype))
-> [HeaderArg ftype] -> Req ftype -> Req ftype
forall a s t. Semigroup a => ASetter s t a a -> a -> s -> t
<>~ [Arg ftype -> HeaderArg ftype
forall ftype. Arg ftype -> HeaderArg ftype
HeaderArg Arg ftype
arg]
where
hname :: Text
hname = String -> Text
pack (String -> Text) -> (Proxy sym -> String) -> Proxy sym -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy sym -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy sym -> Text) -> Proxy sym -> Text
forall a b. (a -> b) -> a -> b
$ (Proxy sym
forall {k} (t :: k). Proxy t
Proxy :: Proxy sym)
arg :: Arg ftype
arg = Arg
{ _argName :: PathSegment
_argName = Text -> PathSegment
PathSegment Text
hname
, _argType :: ftype
_argType = Proxy lang
-> Proxy ftype -> Proxy (RequiredArgument mods a) -> ftype
forall {k} {k} (lang :: k) ftype (a :: k).
HasForeignType lang ftype a =>
Proxy lang -> Proxy ftype -> Proxy a -> ftype
typeFor Proxy lang
lang (Proxy ftype
forall {k} (t :: k). Proxy t
Proxy :: Proxy ftype) (Proxy (RequiredArgument mods a)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (RequiredArgument mods a)) }
subP :: Proxy api
subP = Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api
instance (KnownSymbol sym, HasForeignType lang ftype (RequiredArgument mods a), HasForeign lang ftype api)
=> HasForeign lang ftype (QueryParam' mods sym a :> api) where
type Foreign ftype (QueryParam' mods sym a :> api) = Foreign ftype api
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (QueryParam' mods sym a :> api)
-> Req ftype
-> Foreign ftype (QueryParam' mods sym a :> api)
foreignFor Proxy lang
lang Proxy ftype
Proxy Proxy (QueryParam' mods sym a :> api)
Proxy Req ftype
req =
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang (Proxy ftype
forall {k} (t :: k). Proxy t
Proxy :: Proxy ftype) (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) (Req ftype -> Foreign ftype api) -> Req ftype -> Foreign ftype api
forall a b. (a -> b) -> a -> b
$
Req ftype
req Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (Url ftype -> Identity (Url ftype))
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(Url ftype -> f (Url ftype)) -> Req ftype -> f (Req ftype)
reqUrl((Url ftype -> Identity (Url ftype))
-> Req ftype -> Identity (Req ftype))
-> (([QueryArg ftype] -> Identity [QueryArg ftype])
-> Url ftype -> Identity (Url ftype))
-> ([QueryArg ftype] -> Identity [QueryArg ftype])
-> Req ftype
-> Identity (Req ftype)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.([QueryArg ftype] -> Identity [QueryArg ftype])
-> Url ftype -> Identity (Url ftype)
forall ftype (f :: * -> *).
Functor f =>
([QueryArg ftype] -> f [QueryArg ftype])
-> Url ftype -> f (Url ftype)
queryStr (([QueryArg ftype] -> Identity [QueryArg ftype])
-> Req ftype -> Identity (Req ftype))
-> [QueryArg ftype] -> Req ftype -> Req ftype
forall a s t. Semigroup a => ASetter s t a a -> a -> s -> t
<>~ [Arg ftype -> ArgType -> QueryArg ftype
forall ftype. Arg ftype -> ArgType -> QueryArg ftype
QueryArg Arg ftype
arg ArgType
Normal]
where
str :: Text
str = String -> Text
pack (String -> Text) -> (Proxy sym -> String) -> Proxy sym -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy sym -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy sym -> Text) -> Proxy sym -> Text
forall a b. (a -> b) -> a -> b
$ (Proxy sym
forall {k} (t :: k). Proxy t
Proxy :: Proxy sym)
arg :: Arg ftype
arg = Arg
{ _argName :: PathSegment
_argName = Text -> PathSegment
PathSegment Text
str
, _argType :: ftype
_argType = Proxy lang
-> Proxy ftype -> Proxy (RequiredArgument mods a) -> ftype
forall {k} {k} (lang :: k) ftype (a :: k).
HasForeignType lang ftype a =>
Proxy lang -> Proxy ftype -> Proxy a -> ftype
typeFor Proxy lang
lang (Proxy ftype
forall {k} (t :: k). Proxy t
Proxy :: Proxy ftype) (Proxy (RequiredArgument mods a)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (RequiredArgument mods a)) }
instance
(KnownSymbol sym, HasForeignType lang ftype [a], HasForeign lang ftype api)
=> HasForeign lang ftype (QueryParams sym a :> api) where
type Foreign ftype (QueryParams sym a :> api) = Foreign ftype api
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (QueryParams sym a :> api)
-> Req ftype
-> Foreign ftype (QueryParams sym a :> api)
foreignFor Proxy lang
lang Proxy ftype
Proxy Proxy (QueryParams sym a :> api)
Proxy Req ftype
req =
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang (Proxy ftype
forall {k} (t :: k). Proxy t
Proxy :: Proxy ftype) (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) (Req ftype -> Foreign ftype api) -> Req ftype -> Foreign ftype api
forall a b. (a -> b) -> a -> b
$
Req ftype
req Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (Url ftype -> Identity (Url ftype))
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(Url ftype -> f (Url ftype)) -> Req ftype -> f (Req ftype)
reqUrl((Url ftype -> Identity (Url ftype))
-> Req ftype -> Identity (Req ftype))
-> (([QueryArg ftype] -> Identity [QueryArg ftype])
-> Url ftype -> Identity (Url ftype))
-> ([QueryArg ftype] -> Identity [QueryArg ftype])
-> Req ftype
-> Identity (Req ftype)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.([QueryArg ftype] -> Identity [QueryArg ftype])
-> Url ftype -> Identity (Url ftype)
forall ftype (f :: * -> *).
Functor f =>
([QueryArg ftype] -> f [QueryArg ftype])
-> Url ftype -> f (Url ftype)
queryStr (([QueryArg ftype] -> Identity [QueryArg ftype])
-> Req ftype -> Identity (Req ftype))
-> [QueryArg ftype] -> Req ftype -> Req ftype
forall a s t. Semigroup a => ASetter s t a a -> a -> s -> t
<>~ [Arg ftype -> ArgType -> QueryArg ftype
forall ftype. Arg ftype -> ArgType -> QueryArg ftype
QueryArg Arg ftype
arg ArgType
List]
where
str :: Text
str = String -> Text
pack (String -> Text) -> (Proxy sym -> String) -> Proxy sym -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy sym -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy sym -> Text) -> Proxy sym -> Text
forall a b. (a -> b) -> a -> b
$ (Proxy sym
forall {k} (t :: k). Proxy t
Proxy :: Proxy sym)
arg :: Arg ftype
arg = Arg
{ _argName :: PathSegment
_argName = Text -> PathSegment
PathSegment Text
str
, _argType :: ftype
_argType = Proxy lang -> Proxy ftype -> Proxy [a] -> ftype
forall {k} {k} (lang :: k) ftype (a :: k).
HasForeignType lang ftype a =>
Proxy lang -> Proxy ftype -> Proxy a -> ftype
typeFor Proxy lang
lang (Proxy ftype
forall {k} (t :: k). Proxy t
Proxy :: Proxy ftype) (Proxy [a]
forall {k} (t :: k). Proxy t
Proxy :: Proxy [a]) }
instance
(KnownSymbol sym, HasForeignType lang ftype Bool, HasForeign lang ftype api)
=> HasForeign lang ftype (QueryFlag sym :> api) where
type Foreign ftype (QueryFlag sym :> api) = Foreign ftype api
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (QueryFlag sym :> api)
-> Req ftype
-> Foreign ftype (QueryFlag sym :> api)
foreignFor Proxy lang
lang Proxy ftype
ftype Proxy (QueryFlag sym :> api)
Proxy Req ftype
req =
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
ftype (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) (Req ftype -> Foreign ftype api) -> Req ftype -> Foreign ftype api
forall a b. (a -> b) -> a -> b
$
Req ftype
req Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (Url ftype -> Identity (Url ftype))
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(Url ftype -> f (Url ftype)) -> Req ftype -> f (Req ftype)
reqUrl((Url ftype -> Identity (Url ftype))
-> Req ftype -> Identity (Req ftype))
-> (([QueryArg ftype] -> Identity [QueryArg ftype])
-> Url ftype -> Identity (Url ftype))
-> ([QueryArg ftype] -> Identity [QueryArg ftype])
-> Req ftype
-> Identity (Req ftype)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.([QueryArg ftype] -> Identity [QueryArg ftype])
-> Url ftype -> Identity (Url ftype)
forall ftype (f :: * -> *).
Functor f =>
([QueryArg ftype] -> f [QueryArg ftype])
-> Url ftype -> f (Url ftype)
queryStr (([QueryArg ftype] -> Identity [QueryArg ftype])
-> Req ftype -> Identity (Req ftype))
-> [QueryArg ftype] -> Req ftype -> Req ftype
forall a s t. Semigroup a => ASetter s t a a -> a -> s -> t
<>~ [Arg ftype -> ArgType -> QueryArg ftype
forall ftype. Arg ftype -> ArgType -> QueryArg ftype
QueryArg Arg ftype
arg ArgType
Flag]
where
str :: Text
str = String -> Text
pack (String -> Text) -> (Proxy sym -> String) -> Proxy sym -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy sym -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy sym -> Text) -> Proxy sym -> Text
forall a b. (a -> b) -> a -> b
$ (Proxy sym
forall {k} (t :: k). Proxy t
Proxy :: Proxy sym)
arg :: Arg ftype
arg = Arg
{ _argName :: PathSegment
_argName = Text -> PathSegment
PathSegment Text
str
, _argType :: ftype
_argType = Proxy lang -> Proxy ftype -> Proxy Bool -> ftype
forall {k} {k} (lang :: k) ftype (a :: k).
HasForeignType lang ftype a =>
Proxy lang -> Proxy ftype -> Proxy a -> ftype
typeFor Proxy lang
lang Proxy ftype
ftype (Proxy Bool
forall {k} (t :: k). Proxy t
Proxy :: Proxy Bool) }
instance
(HasForeignType lang ftype (Maybe a), HasForeign lang ftype api)
=> HasForeign lang ftype (Fragment a :> api) where
type Foreign ftype (Fragment a :> api) = Foreign ftype api
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (Fragment a :> api)
-> Req ftype
-> Foreign ftype (Fragment a :> api)
foreignFor Proxy lang
lang Proxy ftype
Proxy Proxy (Fragment a :> api)
Proxy Req ftype
req =
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang (Proxy ftype
forall {k} (t :: k). Proxy t
Proxy :: Proxy ftype) (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) (Req ftype -> Foreign ftype api) -> Req ftype -> Foreign ftype api
forall a b. (a -> b) -> a -> b
$
Req ftype
req Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (Url ftype -> Identity (Url ftype))
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(Url ftype -> f (Url ftype)) -> Req ftype -> f (Req ftype)
reqUrl ((Url ftype -> Identity (Url ftype))
-> Req ftype -> Identity (Req ftype))
-> ((Maybe ftype -> Identity (Maybe ftype))
-> Url ftype -> Identity (Url ftype))
-> (Maybe ftype -> Identity (Maybe ftype))
-> Req ftype
-> Identity (Req ftype)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe ftype -> Identity (Maybe ftype))
-> Url ftype -> Identity (Url ftype)
forall ftype (f :: * -> *).
Functor f =>
(Maybe ftype -> f (Maybe ftype)) -> Url ftype -> f (Url ftype)
frag ((Maybe ftype -> Identity (Maybe ftype))
-> Req ftype -> Identity (Req ftype))
-> Maybe ftype -> Req ftype -> Req ftype
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ftype -> Maybe ftype
forall a. a -> Maybe a
Just ftype
argT
where
argT :: ftype
argT = Proxy lang -> Proxy ftype -> Proxy (Maybe a) -> ftype
forall {k} {k} (lang :: k) ftype (a :: k).
HasForeignType lang ftype a =>
Proxy lang -> Proxy ftype -> Proxy a -> ftype
typeFor Proxy lang
lang (Proxy ftype
forall {k} (t :: k). Proxy t
Proxy :: Proxy ftype) (Proxy (Maybe a)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (Maybe a))
instance HasForeign lang ftype Raw where
type Foreign ftype Raw = HTTP.Method -> Req ftype
foreignFor :: Proxy lang
-> Proxy ftype -> Proxy Raw -> Req ftype -> Foreign ftype Raw
foreignFor Proxy lang
_ Proxy ftype
Proxy Proxy Raw
Proxy Req ftype
req Method
method =
Req ftype
req Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (FunctionName -> Identity FunctionName)
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(FunctionName -> f FunctionName) -> Req ftype -> f (Req ftype)
reqFuncName ((FunctionName -> Identity FunctionName)
-> Req ftype -> Identity (Req ftype))
-> (([Text] -> Identity [Text])
-> FunctionName -> Identity FunctionName)
-> ([Text] -> Identity [Text])
-> Req ftype
-> Identity (Req ftype)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Text] -> Identity [Text])
-> FunctionName -> Identity FunctionName
Iso' FunctionName [Text]
_FunctionName (([Text] -> Identity [Text]) -> Req ftype -> Identity (Req ftype))
-> ([Text] -> [Text]) -> Req ftype -> Req ftype
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ((Text -> Text
toLower (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Method -> Text
decodeUtf8 Method
method) Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:)
Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (Method -> Identity Method) -> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(Method -> f Method) -> Req ftype -> f (Req ftype)
reqMethod ((Method -> Identity Method) -> Req ftype -> Identity (Req ftype))
-> Method -> Req ftype -> Req ftype
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Method
method
instance (Elem JSON list, HasForeignType lang ftype a, HasForeign lang ftype api)
=> HasForeign lang ftype (ReqBody' mods list a :> api) where
type Foreign ftype (ReqBody' mods list a :> api) = Foreign ftype api
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (ReqBody' mods list a :> api)
-> Req ftype
-> Foreign ftype (ReqBody' mods list a :> api)
foreignFor Proxy lang
lang Proxy ftype
ftype Proxy (ReqBody' mods list a :> api)
Proxy Req ftype
req =
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
ftype (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) (Req ftype -> Foreign ftype api) -> Req ftype -> Foreign ftype api
forall a b. (a -> b) -> a -> b
$
Req ftype
req Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (Maybe ftype -> Identity (Maybe ftype))
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(Maybe ftype -> f (Maybe ftype)) -> Req ftype -> f (Req ftype)
reqBody ((Maybe ftype -> Identity (Maybe ftype))
-> Req ftype -> Identity (Req ftype))
-> Maybe ftype -> Req ftype -> Req ftype
forall s t a b. ASetter s t a b -> b -> s -> t
.~ (ftype -> Maybe ftype
forall a. a -> Maybe a
Just (ftype -> Maybe ftype) -> ftype -> Maybe ftype
forall a b. (a -> b) -> a -> b
$ Proxy lang -> Proxy ftype -> Proxy a -> ftype
forall {k} {k} (lang :: k) ftype (a :: k).
HasForeignType lang ftype a =>
Proxy lang -> Proxy ftype -> Proxy a -> ftype
typeFor Proxy lang
lang Proxy ftype
ftype (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a))
instance
( HasForeign lang ftype api
) => HasForeign lang ftype (StreamBody' mods framing ctype a :> api)
where
type Foreign ftype (StreamBody' mods framing ctype a :> api) = Foreign ftype api
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (StreamBody' mods framing ctype a :> api)
-> Req ftype
-> Foreign ftype (StreamBody' mods framing ctype a :> api)
foreignFor Proxy lang
_lang Proxy ftype
Proxy Proxy (StreamBody' mods framing ctype a :> api)
Proxy Req ftype
_req = String -> Foreign ftype api
forall a. HasCallStack => String -> a
error String
"HasForeign @StreamBody"
instance (KnownSymbol path, HasForeign lang ftype api)
=> HasForeign lang ftype (path :> api) where
type Foreign ftype (path :> api) = Foreign ftype api
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (path :> api)
-> Req ftype
-> Foreign ftype (path :> api)
foreignFor Proxy lang
lang Proxy ftype
ftype Proxy (path :> api)
Proxy Req ftype
req =
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
ftype (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) (Req ftype -> Foreign ftype api) -> Req ftype -> Foreign ftype api
forall a b. (a -> b) -> a -> b
$
Req ftype
req Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (Url ftype -> Identity (Url ftype))
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(Url ftype -> f (Url ftype)) -> Req ftype -> f (Req ftype)
reqUrl ((Url ftype -> Identity (Url ftype))
-> Req ftype -> Identity (Req ftype))
-> ((Path ftype -> Identity (Path ftype))
-> Url ftype -> Identity (Url ftype))
-> (Path ftype -> Identity (Path ftype))
-> Req ftype
-> Identity (Req ftype)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Path ftype -> Identity (Path ftype))
-> Url ftype -> Identity (Url ftype)
forall ftype (f :: * -> *).
Functor f =>
(Path ftype -> f (Path ftype)) -> Url ftype -> f (Url ftype)
path ((Path ftype -> Identity (Path ftype))
-> Req ftype -> Identity (Req ftype))
-> Path ftype -> Req ftype -> Req ftype
forall a s t. Semigroup a => ASetter s t a a -> a -> s -> t
<>~ [SegmentType ftype -> Segment ftype
forall ftype. SegmentType ftype -> Segment ftype
Segment (PathSegment -> SegmentType ftype
forall ftype. PathSegment -> SegmentType ftype
Static (Text -> PathSegment
PathSegment Text
str))]
Req ftype -> (Req ftype -> Req ftype) -> Req ftype
forall a b. a -> (a -> b) -> b
& (FunctionName -> Identity FunctionName)
-> Req ftype -> Identity (Req ftype)
forall ftype (f :: * -> *).
Functor f =>
(FunctionName -> f FunctionName) -> Req ftype -> f (Req ftype)
reqFuncName ((FunctionName -> Identity FunctionName)
-> Req ftype -> Identity (Req ftype))
-> (([Text] -> Identity [Text])
-> FunctionName -> Identity FunctionName)
-> ([Text] -> Identity [Text])
-> Req ftype
-> Identity (Req ftype)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Text] -> Identity [Text])
-> FunctionName -> Identity FunctionName
Iso' FunctionName [Text]
_FunctionName (([Text] -> Identity [Text]) -> Req ftype -> Identity (Req ftype))
-> ([Text] -> [Text]) -> Req ftype -> Req ftype
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ([Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
str])
where
str :: Text
str = String -> Text
pack (String -> Text) -> (Proxy path -> String) -> Proxy path -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy path -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy path -> Text) -> Proxy path -> Text
forall a b. (a -> b) -> a -> b
$ (Proxy path
forall {k} (t :: k). Proxy t
Proxy :: Proxy path)
instance HasForeign lang ftype api
=> HasForeign lang ftype (RemoteHost :> api) where
type Foreign ftype (RemoteHost :> api) = Foreign ftype api
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (RemoteHost :> api)
-> Req ftype
-> Foreign ftype (RemoteHost :> api)
foreignFor Proxy lang
lang Proxy ftype
ftype Proxy (RemoteHost :> api)
Proxy Req ftype
req =
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
ftype (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) Req ftype
req
instance HasForeign lang ftype api
=> HasForeign lang ftype (IsSecure :> api) where
type Foreign ftype (IsSecure :> api) = Foreign ftype api
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (IsSecure :> api)
-> Req ftype
-> Foreign ftype (IsSecure :> api)
foreignFor Proxy lang
lang Proxy ftype
ftype Proxy (IsSecure :> api)
Proxy Req ftype
req =
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
ftype (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) Req ftype
req
instance HasForeign lang ftype api => HasForeign lang ftype (Vault :> api) where
type Foreign ftype (Vault :> api) = Foreign ftype api
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (Vault :> api)
-> Req ftype
-> Foreign ftype (Vault :> api)
foreignFor Proxy lang
lang Proxy ftype
ftype Proxy (Vault :> api)
Proxy Req ftype
req =
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
ftype (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) Req ftype
req
instance HasForeign lang ftype api =>
HasForeign lang ftype (WithNamedContext name context api) where
type Foreign ftype (WithNamedContext name context api) = Foreign ftype api
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (WithNamedContext name context api)
-> Req ftype
-> Foreign ftype (WithNamedContext name context api)
foreignFor Proxy lang
lang Proxy ftype
ftype Proxy (WithNamedContext name context api)
Proxy = Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
ftype (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api)
instance HasForeign lang ftype api =>
HasForeign lang ftype (WithResource res :> api) where
type Foreign ftype (WithResource res :> api) = Foreign ftype api
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (WithResource res :> api)
-> Req ftype
-> Foreign ftype (WithResource res :> api)
foreignFor Proxy lang
lang Proxy ftype
ftype Proxy (WithResource res :> api)
Proxy = Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
ftype (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api)
instance HasForeign lang ftype api
=> HasForeign lang ftype (HttpVersion :> api) where
type Foreign ftype (HttpVersion :> api) = Foreign ftype api
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (HttpVersion :> api)
-> Req ftype
-> Foreign ftype (HttpVersion :> api)
foreignFor Proxy lang
lang Proxy ftype
ftype Proxy (HttpVersion :> api)
Proxy Req ftype
req =
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
ftype (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) Req ftype
req
instance HasForeign lang ftype api
=> HasForeign lang ftype (Summary desc :> api) where
type Foreign ftype (Summary desc :> api) = Foreign ftype api
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (Summary desc :> api)
-> Req ftype
-> Foreign ftype (Summary desc :> api)
foreignFor Proxy lang
lang Proxy ftype
ftype Proxy (Summary desc :> api)
Proxy Req ftype
req =
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
ftype (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) Req ftype
req
instance HasForeign lang ftype api
=> HasForeign lang ftype (Description desc :> api) where
type Foreign ftype (Description desc :> api) = Foreign ftype api
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (Description desc :> api)
-> Req ftype
-> Foreign ftype (Description desc :> api)
foreignFor Proxy lang
lang Proxy ftype
ftype Proxy (Description desc :> api)
Proxy Req ftype
req =
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
ftype (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) Req ftype
req
instance HasForeign lang ftype (ToServantApi r) => HasForeign lang ftype (NamedRoutes r) where
type Foreign ftype (NamedRoutes r) = Foreign ftype (ToServantApi r)
foreignFor :: Proxy lang
-> Proxy ftype
-> Proxy (NamedRoutes r)
-> Req ftype
-> Foreign ftype (NamedRoutes r)
foreignFor Proxy lang
lang Proxy ftype
ftype Proxy (NamedRoutes r)
Proxy Req ftype
req =
Proxy lang
-> Proxy ftype
-> Proxy (ToServantApi r)
-> Req ftype
-> Foreign ftype (ToServantApi r)
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
ftype (Proxy (ToServantApi r)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (ToServantApi r)) Req ftype
req
class GenerateList ftype reqs where
generateList :: reqs -> [Req ftype]
instance GenerateList ftype EmptyForeignAPI where
generateList :: EmptyForeignAPI -> [Req ftype]
generateList EmptyForeignAPI
_ = []
instance GenerateList ftype (Req ftype) where
generateList :: Req ftype -> [Req ftype]
generateList Req ftype
r = [Req ftype
r]
instance (GenerateList ftype start, GenerateList ftype rest)
=> GenerateList ftype (start :<|> rest) where
generateList :: (start :<|> rest) -> [Req ftype]
generateList (start
start :<|> rest
rest) = (start -> [Req ftype]
forall ftype reqs. GenerateList ftype reqs => reqs -> [Req ftype]
generateList start
start) [Req ftype] -> [Req ftype] -> [Req ftype]
forall a. [a] -> [a] -> [a]
++ (rest -> [Req ftype]
forall ftype reqs. GenerateList ftype reqs => reqs -> [Req ftype]
generateList rest
rest)
listFromAPI
:: (HasForeign lang ftype api, GenerateList ftype (Foreign ftype api))
=> Proxy lang
-> Proxy ftype
-> Proxy api
-> [Req ftype]
listFromAPI :: forall {k} (lang :: k) ftype api.
(HasForeign lang ftype api,
GenerateList ftype (Foreign ftype api)) =>
Proxy lang -> Proxy ftype -> Proxy api -> [Req ftype]
listFromAPI Proxy lang
lang Proxy ftype
ftype Proxy api
p = Foreign ftype api -> [Req ftype]
forall ftype reqs. GenerateList ftype reqs => reqs -> [Req ftype]
generateList (Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
forall {k} (lang :: k) ftype api.
HasForeign lang ftype api =>
Proxy lang
-> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
foreignFor Proxy lang
lang Proxy ftype
ftype Proxy api
p Req ftype
forall ftype. Req ftype
defReq)