module Servant.API.Routes.Path
( Path
, prependPathPart
, prependCapturePart
, prependCaptureAllPart
, renderPath
, rootPath
)
where
import qualified Data.Text as T
import Data.Typeable
import "this" Servant.API.Routes.Internal.Path
import "this" Servant.API.Routes.Utils
rootPath :: Path
rootPath :: Path
rootPath = [PathPart] -> Path
Path []
prependPathPart :: T.Text -> Path -> Path
prependPathPart :: Text -> Path -> Path
prependPathPart Text
part (Path [PathPart]
parts) =
[PathPart] -> Path
Path ([PathPart]
splitParts [PathPart] -> [PathPart] -> [PathPart]
forall a. Semigroup a => a -> a -> a
<> [PathPart]
parts)
where
splitParts :: [PathPart]
splitParts = (Text -> PathPart) -> [Text] -> [PathPart]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> PathPart
StringPart ([Text] -> [PathPart])
-> ([Text] -> [Text]) -> [Text] -> [PathPart]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Text -> Bool) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Bool
T.null) ([Text] -> [PathPart]) -> [Text] -> [PathPart]
forall a b. (a -> b) -> a -> b
$ HasCallStack => Text -> Text -> [Text]
Text -> Text -> [Text]
T.splitOn Text
pathSeparator Text
part
prependCapturePart ::
forall a.
(Typeable a) =>
T.Text ->
Path ->
Path
prependCapturePart :: forall a. Typeable a => Text -> Path -> Path
prependCapturePart Text
name (Path [PathPart]
parts) =
[PathPart] -> Path
Path (PathPart
capture PathPart -> [PathPart] -> [PathPart]
forall a. a -> [a] -> [a]
: [PathPart]
parts)
where
capture :: PathPart
capture = Text -> TypeRep -> PathPart
CapturePart Text
name (TypeRep -> PathPart) -> TypeRep -> PathPart
forall a b. (a -> b) -> a -> b
$ forall a. Typeable a => TypeRep
typeRepOf @a
prependCaptureAllPart ::
forall a.
(Typeable a) =>
T.Text ->
Path ->
Path
prependCaptureAllPart :: forall a. Typeable a => Text -> Path -> Path
prependCaptureAllPart Text
name (Path [PathPart]
parts) =
[PathPart] -> Path
Path (PathPart
capture PathPart -> [PathPart] -> [PathPart]
forall a. a -> [a] -> [a]
: [PathPart]
parts)
where
capture :: PathPart
capture = Text -> TypeRep -> PathPart
CaptureAllPart Text
name (TypeRep -> PathPart) -> TypeRep -> PathPart
forall a b. (a -> b) -> a -> b
$ forall a. Typeable a => TypeRep
typeRepOf @a