{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ExistentialQuantification #-}
module Servant.API.NamedArgs where
import GHC.TypeLits (Symbol, KnownSymbol, symbolVal)
import Data.Functor.Identity (Identity)
import Data.Proxy (Proxy(..))
import Data.Text (Text)
import Named ((:!), (:?), arg, argF, Name(..), (!), NamedF(..), pattern Arg
, argDef)
import Servant.API ((:>), (:<|>)(..), Capture', If, QueryFlag, QueryParam'
, QueryParams, SBoolI(..), SBool(..), HasLink(..)
, ToHttpApiData(..), CaptureAll(..), AddHeader(..), Headers(..)
, Header'(..), ReqBody')
import Servant.API.Modifiers (FoldRequired, Optional, Required, Strict, FoldLenient)
import Servant.API.Generic (GenericMode(..), AsApi, ToServant)
import Servant.Links (Param(..), Link(..), linkQueryParams)
import Type.Reflection (Typeable)
import GHC.Generics
data NamedCapture' (mods :: [*]) (sym :: Symbol) (a :: *)
deriving Typeable
type NamedCapture = NamedCapture' '[]
instance (ToHttpApiData v, HasLink sub, KnownSymbol name)
=> HasLink (NamedCapture' mods name v :> sub) where
type MkLink (NamedCapture' mods name v :> sub) a = (name :! v) -> MkLink sub a
toLink toA _ l (arg (Name @name) -> capture)
= (toLink toA (Proxy @(Capture' mods name v :> sub)) l) capture
data NamedCaptureAll (sym :: Symbol) (a :: *)
deriving Typeable
instance (ToHttpApiData v, HasLink sub, KnownSymbol name)
=> HasLink (NamedCaptureAll name v :> sub) where
type MkLink (NamedCaptureAll name v :> sub) a = (name :? [v]) -> MkLink sub a
toLink toA _ l (argDef (Name @name) [] -> capture)
= (toLink toA (Proxy @(CaptureAll name v :> sub)) l) capture
data NamedParam (mods :: [*]) (sym :: Symbol) (a :: *)
deriving Typeable
type RequiredNamedParam = NamedParam '[Required, Strict]
type OptionalNamedParam = NamedParam '[Optional, Strict]
instance (KnownSymbol name, HasLink sub, ToHttpApiData v, SBoolI (FoldRequired mods))
=> HasLink (NamedParam mods name v :> sub) where
type MkLink (NamedParam mods name v :> sub) a
= RequiredNamedArgument mods name v -> MkLink sub a
toLink toA _ l =
foldRequiredAdapter @mods @name @v (toLink toA (Proxy @(QueryParam' mods name v :> sub)) l)
data NamedParams (sym :: Symbol) (a :: *)
deriving Typeable
instance (KnownSymbol name, HasLink sub, ToHttpApiData v)
=> HasLink (NamedParams name v :> sub) where
type MkLink (NamedParams name v :> sub) a = (name :! [v]) -> MkLink sub a
toLink toA _ l (arg (Name @name) -> vs)
= (toLink toA (Proxy @(QueryParams name v :> sub)) l) vs
data NamedFlag (sym :: Symbol)
deriving Typeable
instance (KnownSymbol name, HasLink sub)
=> HasLink (NamedFlag name :> sub) where
type MkLink (NamedFlag name :> sub) a =
(name :? Bool) -> MkLink sub a
toLink toA _ l (argDef (Name @name) False -> v) =
(toLink toA (Proxy @(QueryFlag name :> sub)) l) v
data NamedHeader' (mods :: [*]) (sym :: Symbol) (a :: *)
deriving Typeable
type NamedHeader = NamedHeader' '[Optional, Strict]
instance (HasLink sub) => HasLink (NamedHeader' mods name a :> sub) where
type MkLink (NamedHeader' mods name a :> sub) r = MkLink sub r
toLink toA _ = toLink toA (Proxy :: Proxy sub)
data NamedBody' (mods :: [*]) (sym :: Symbol) (contentTypes :: [*]) (a :: *) deriving Typeable
type NamedBody = NamedBody' '[Required, Strict]
instance (HasLink sub) => HasLink (NamedBody' mods name ct a :> sub) where
type MkLink (NamedBody' mods name ct a :> sub) r = MkLink sub r
toLink toA _ = toLink toA (Proxy :: Proxy sub)
type RequiredNamedArgument mods name a = If (FoldRequired mods) (name :! a) (name :? a)
type RequestNamedArgument mods name a
= If (FoldRequired mods)
(name :! If (FoldLenient mods) (Either Text a) a)
(name :? (If (FoldLenient mods) (Either Text a) a))
foldRequiredNamedArgument
:: forall mods name a r. (SBoolI (FoldRequired mods), KnownSymbol name)
=> (a -> r)
-> (Maybe a -> r)
-> RequiredNamedArgument mods name a
-> r
foldRequiredNamedArgument f g mx =
case (sbool :: SBool (FoldRequired mods), mx) of
(STrue, (arg (Name :: Name name) -> x)) -> f x
(SFalse, (argF (Name :: Name name) -> x)) -> g x
foldRequiredAdapter
:: forall mods name a r. (SBoolI (FoldRequired mods), KnownSymbol name)
=> (If (FoldRequired mods) a (Maybe a) -> r)
-> RequiredNamedArgument mods name a
-> r
foldRequiredAdapter f mv =
case (sbool :: SBool (FoldRequired mods), mv) of
(STrue, (arg (Name :: Name name) -> x)) -> f x
(SFalse, (argF (Name :: Name name) -> x)) -> f x
unfoldRequestNamedArgument
:: forall mods name m a. (Monad m, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods))
=> m (RequestNamedArgument mods name a)
-> (Text -> m (RequestNamedArgument mods name a))
-> Maybe (Either Text a)
-> m (RequestNamedArgument mods name a)
unfoldRequestNamedArgument errReq errSt mex =
case (sbool :: SBool (FoldRequired mods), mex, sbool :: SBool (FoldLenient mods)) of
(STrue, Nothing, _) -> errReq
(SFalse, Nothing, _) -> pure $ ArgF Nothing
(STrue, Just ex, STrue) -> pure $ Arg ex
(STrue, Just ex, SFalse) -> either errSt pure (Arg <$> ex)
(SFalse, Just ex, STrue) -> pure $ ArgF $ Just ex
(SFalse, Just ex, SFalse) -> either errSt (pure . ArgF . Just) ex
type family Transform (t :: [Transformation]) (api :: k) :: k where
Transform t (a :<|> b) = Transform t a :<|> Transform t b
Transform t (a :> b) = Transform t a :> Transform t b
Transform (NameParams:_) (QueryParam' mods sym a)
= NamedParam mods sym a
Transform (NameMultiParams:_) (QueryParams sym a)
= NamedParams sym a
Transform (NameFlags:_) (QueryFlag sym)
= NamedFlag sym
Transform (NameCaptures:_) (Capture' mods sym a)
= NamedCapture' mods sym a
Transform (NameCaptureAlls:_) (CaptureAll sym a)
= NamedCaptureAll sym a
Transform (NameHeaders:_) (Header' mods sym a)
= NamedHeader' mods sym a
Transform (NameBodies name:_) (ReqBody' mods ct a)
= NamedBody' mods name ct a
Transform (UnnameParams:_) (NamedParam mods sym a)
= QueryParam' mods sym a
Transform (UnnameMultiParams:_) (NamedParams sym a)
= QueryParams sym a
Transform (UnnameFlags:_) (NamedFlag sym)
= QueryFlag sym
Transform (UnnameCaptures:_) (NamedCapture' mods sym a)
= Capture' mods sym a
Transform (UnnameCaptureAlls:_) (NamedCaptureAll sym a)
= CaptureAll sym a
Transform (UnnameHeaders:_) (NamedHeader' mods sym a)
= Header' mods sym a
Transform (UnnameBodies:_) (NamedBody' mods sym ct a)
= ReqBody' mods ct a
Transform (_:ts) a = Transform ts a
Transform '[] a = a
data AsTransformed (t :: [Transformation]) (m :: *)
instance (GenericMode mode) => GenericMode (AsTransformed t mode) where
type AsTransformed t mode :- api = mode :- Transform t api
data Transformation = NameParams
| NameMultiParams
| NameCaptures
| NameCaptureAlls
| NameFlags
| NameHeaders
| forall name. NameBodies name
| UnnameParams
| UnnameMultiParams
| UnnameCaptures
| UnnameCaptureAlls
| UnnameFlags
| UnnameHeaders
| UnnameBodies