module Servant.Utils.Links (
module Servant.API.TypeLevel,
safeLink
, allLinks
, URI(..)
, HasLink(..)
, Link
, linkURI
, linkURI'
, LinkArrayElementStyle (..)
, Param (..)
, linkSegments
, linkQueryParams
) where
import Data.List
import Data.Semigroup ((<>))
import Data.Proxy ( Proxy(..) )
import Data.Singletons.Bool ( SBool (..), SBoolI (..) )
import qualified Data.Text as Text
import qualified Data.Text.Encoding as TE
import Data.Type.Bool (If)
import GHC.TypeLits ( KnownSymbol, symbolVal )
import Network.URI ( URI(..), escapeURIString, isUnreserved )
import Prelude ()
import Prelude.Compat
import Web.HttpApiData
import Servant.API.Alternative ( (:<|>)((:<|>)) )
import Servant.API.BasicAuth ( BasicAuth )
import Servant.API.Capture ( Capture', CaptureAll )
import Servant.API.ReqBody ( ReqBody' )
import Servant.API.QueryParam ( QueryParam', QueryParams, QueryFlag )
import Servant.API.Header ( Header' )
import Servant.API.HttpVersion (HttpVersion)
import Servant.API.RemoteHost ( RemoteHost )
import Servant.API.IsSecure (IsSecure)
import Servant.API.Empty (EmptyAPI (..))
import Servant.API.Verbs ( Verb )
import Servant.API.Sub ( type (:>) )
import Servant.API.Raw ( Raw )
import Servant.API.Stream ( Stream )
import Servant.API.TypeLevel
import Servant.API.Modifiers (FoldRequired)
import Servant.API.Description (Description, Summary)
import Servant.API.Vault (Vault)
import Servant.API.WithNamedContext (WithNamedContext)
import Servant.API.Experimental.Auth ( AuthProtect )
data Link = Link
{ _segments :: [Escaped]
, _queryParams :: [Param]
} deriving Show
newtype Escaped = Escaped String
escaped :: String -> Escaped
escaped = Escaped . escapeURIString isUnreserved
getEscaped :: Escaped -> String
getEscaped (Escaped s) = s
instance Show Escaped where
showsPrec d (Escaped s) = showsPrec d s
show (Escaped s) = show s
linkSegments :: Link -> [String]
linkSegments = map getEscaped . _segments
linkQueryParams :: Link -> [Param]
linkQueryParams = _queryParams
instance ToHttpApiData Link where
toHeader = TE.encodeUtf8 . toUrlPiece
toUrlPiece l =
let uri = linkURI l
in Text.pack $ uriPath uri ++ uriQuery uri
data Param
= SingleParam String Text.Text
| ArrayElemParam String Text.Text
| FlagParam String
deriving Show
addSegment :: Escaped -> Link -> Link
addSegment seg l = l { _segments = _segments l <> [seg] }
addQueryParam :: Param -> Link -> Link
addQueryParam qp l =
l { _queryParams = _queryParams l <> [qp] }
linkURI :: Link -> URI
linkURI = linkURI' LinkArrayElementBracket
data LinkArrayElementStyle
= LinkArrayElementBracket
| LinkArrayElementPlain
deriving (Eq, Ord, Show, Enum, Bounded)
linkURI' :: LinkArrayElementStyle -> Link -> URI
linkURI' addBrackets (Link segments q_params) =
URI mempty
Nothing
(intercalate "/" $ map getEscaped segments)
(makeQueries q_params) mempty
where
makeQueries :: [Param] -> String
makeQueries [] = ""
makeQueries xs =
"?" <> intercalate "&" (fmap makeQuery xs)
makeQuery :: Param -> String
makeQuery (ArrayElemParam k v) = escape k <> style <> escape (Text.unpack v)
makeQuery (SingleParam k v) = escape k <> "=" <> escape (Text.unpack v)
makeQuery (FlagParam k) = escape k
style = case addBrackets of
LinkArrayElementBracket -> "[]="
LinkArrayElementPlain -> "="
escape :: String -> String
escape = escapeURIString isUnreserved
safeLink
:: forall endpoint api. (IsElem endpoint api, HasLink endpoint)
=> Proxy api
-> Proxy endpoint
-> MkLink endpoint
safeLink _ endpoint = toLink endpoint (Link mempty mempty)
allLinks
:: forall api. HasLink api
=> Proxy api
-> MkLink api
allLinks api = toLink api (Link mempty mempty)
class HasLink endpoint where
type MkLink endpoint
toLink :: Proxy endpoint
-> Link
-> MkLink endpoint
instance (KnownSymbol sym, HasLink sub) => HasLink (sym :> sub) where
type MkLink (sym :> sub) = MkLink sub
toLink _ =
toLink (Proxy :: Proxy sub) . addSegment (escaped seg)
where
seg = symbolVal (Proxy :: Proxy sym)
instance (KnownSymbol sym, ToHttpApiData v, HasLink sub, SBoolI (FoldRequired mods))
=> HasLink (QueryParam' mods sym v :> sub) where
type MkLink (QueryParam' mods sym v :> sub) = If (FoldRequired mods) v (Maybe v) -> MkLink sub
toLink _ l mv =
toLink (Proxy :: Proxy sub) $
case sbool :: SBool (FoldRequired mods) of
STrue -> (addQueryParam . SingleParam k . toQueryParam) mv l
SFalse -> maybe id (addQueryParam . SingleParam k . toQueryParam) mv l
where
k :: String
k = symbolVal (Proxy :: Proxy sym)
instance (KnownSymbol sym, ToHttpApiData v, HasLink sub)
=> HasLink (QueryParams sym v :> sub) where
type MkLink (QueryParams sym v :> sub) = [v] -> MkLink sub
toLink _ l =
toLink (Proxy :: Proxy sub) .
foldl' (\l' v -> addQueryParam (ArrayElemParam k (toQueryParam v)) l') l
where
k = symbolVal (Proxy :: Proxy sym)
instance (KnownSymbol sym, HasLink sub)
=> HasLink (QueryFlag sym :> sub) where
type MkLink (QueryFlag sym :> sub) = Bool -> MkLink sub
toLink _ l False =
toLink (Proxy :: Proxy sub) l
toLink _ l True =
toLink (Proxy :: Proxy sub) $ addQueryParam (FlagParam k) l
where
k = symbolVal (Proxy :: Proxy sym)
instance (HasLink a, HasLink b) => HasLink (a :<|> b) where
type MkLink (a :<|> b) = MkLink a :<|> MkLink b
toLink _ l = toLink (Proxy :: Proxy a) l :<|> toLink (Proxy :: Proxy b) l
instance HasLink sub => HasLink (ReqBody' mods ct a :> sub) where
type MkLink (ReqBody' mods ct a :> sub) = MkLink sub
toLink _ = toLink (Proxy :: Proxy sub)
instance (ToHttpApiData v, HasLink sub)
=> HasLink (Capture' mods sym v :> sub) where
type MkLink (Capture' mods sym v :> sub) = v -> MkLink sub
toLink _ l v =
toLink (Proxy :: Proxy sub) $
addSegment (escaped . Text.unpack $ toUrlPiece v) l
instance (ToHttpApiData v, HasLink sub)
=> HasLink (CaptureAll sym v :> sub) where
type MkLink (CaptureAll sym v :> sub) = [v] -> MkLink sub
toLink _ l vs =
toLink (Proxy :: Proxy sub) $
foldl' (flip $ addSegment . escaped . Text.unpack . toUrlPiece) l vs
instance HasLink sub => HasLink (Header' mods sym a :> sub) where
type MkLink (Header' mods sym a :> sub) = MkLink sub
toLink _ = toLink (Proxy :: Proxy sub)
instance HasLink sub => HasLink (Vault :> sub) where
type MkLink (Vault :> sub) = MkLink sub
toLink _ = toLink (Proxy :: Proxy sub)
instance HasLink sub => HasLink (Description s :> sub) where
type MkLink (Description s :> sub) = MkLink sub
toLink _ = toLink (Proxy :: Proxy sub)
instance HasLink sub => HasLink (Summary s :> sub) where
type MkLink (Summary s :> sub) = MkLink sub
toLink _ = toLink (Proxy :: Proxy sub)
instance HasLink sub => HasLink (HttpVersion :> sub) where
type MkLink (HttpVersion:> sub) = MkLink sub
toLink _ = toLink (Proxy :: Proxy sub)
instance HasLink sub => HasLink (IsSecure :> sub) where
type MkLink (IsSecure :> sub) = MkLink sub
toLink _ = toLink (Proxy :: Proxy sub)
instance HasLink sub => HasLink (WithNamedContext name context sub) where
type MkLink (WithNamedContext name context sub) = MkLink sub
toLink _ = toLink (Proxy :: Proxy sub)
instance HasLink sub => HasLink (RemoteHost :> sub) where
type MkLink (RemoteHost :> sub) = MkLink sub
toLink _ = toLink (Proxy :: Proxy sub)
instance HasLink sub => HasLink (BasicAuth realm a :> sub) where
type MkLink (BasicAuth realm a :> sub) = MkLink sub
toLink _ = toLink (Proxy :: Proxy sub)
instance HasLink EmptyAPI where
type MkLink EmptyAPI = EmptyAPI
toLink _ _ = EmptyAPI
instance HasLink (Verb m s ct a) where
type MkLink (Verb m s ct a) = Link
toLink _ = id
instance HasLink Raw where
type MkLink Raw = Link
toLink _ = id
instance HasLink (Stream m fr ct a) where
type MkLink (Stream m fr ct a) = Link
toLink _ = id
instance HasLink sub => HasLink (AuthProtect tag :> sub) where
type MkLink (AuthProtect tag :> sub) = MkLink sub
toLink _ = toLink (Proxy :: Proxy sub)