{-# OPTIONS_HADDOCK not-home #-}
module Servant.API.Routes.Internal.Path
( Path (..)
, renderPath
, pathSeparator
, PathPart (..)
)
where
import Data.Aeson
import Data.String
import qualified Data.Text as T
import Data.Typeable
data PathPart
=
StringPart T.Text
|
CapturePart T.Text TypeRep
|
CaptureAllPart T.Text TypeRep
deriving (PathPart -> PathPart -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PathPart -> PathPart -> Bool
$c/= :: PathPart -> PathPart -> Bool
== :: PathPart -> PathPart -> Bool
$c== :: PathPart -> PathPart -> Bool
Eq, Eq PathPart
PathPart -> PathPart -> Bool
PathPart -> PathPart -> Ordering
PathPart -> PathPart -> PathPart
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PathPart -> PathPart -> PathPart
$cmin :: PathPart -> PathPart -> PathPart
max :: PathPart -> PathPart -> PathPart
$cmax :: PathPart -> PathPart -> PathPart
>= :: PathPart -> PathPart -> Bool
$c>= :: PathPart -> PathPart -> Bool
> :: PathPart -> PathPart -> Bool
$c> :: PathPart -> PathPart -> Bool
<= :: PathPart -> PathPart -> Bool
$c<= :: PathPart -> PathPart -> Bool
< :: PathPart -> PathPart -> Bool
$c< :: PathPart -> PathPart -> Bool
compare :: PathPart -> PathPart -> Ordering
$ccompare :: PathPart -> PathPart -> Ordering
Ord)
instance IsString PathPart where
fromString :: String -> PathPart
fromString = Text -> PathPart
StringPart forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
instance Show PathPart where
show :: PathPart -> String
show = Text -> String
T.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. PathPart -> Text
renderPathPart
renderPathPart :: PathPart -> T.Text
renderPathPart :: PathPart -> Text
renderPathPart = \case
StringPart Text
t -> Text
t
CapturePart Text
_ TypeRep
typ -> Text
"<" forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (forall a. Show a => a -> String
show TypeRep
typ) forall a. Semigroup a => a -> a -> a
<> Text
">"
CaptureAllPart Text
_ TypeRep
typ -> Text
"<[" forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (forall a. Show a => a -> String
show TypeRep
typ) forall a. Semigroup a => a -> a -> a
<> Text
"]>"
pathSeparator :: T.Text
pathSeparator :: Text
pathSeparator = Text
"/"
newtype Path = Path
{ Path -> [PathPart]
unPath :: [PathPart]
}
deriving (Path -> Path -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Path -> Path -> Bool
$c/= :: Path -> Path -> Bool
== :: Path -> Path -> Bool
$c== :: Path -> Path -> Bool
Eq, Eq Path
Path -> Path -> Bool
Path -> Path -> Ordering
Path -> Path -> Path
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Path -> Path -> Path
$cmin :: Path -> Path -> Path
max :: Path -> Path -> Path
$cmax :: Path -> Path -> Path
>= :: Path -> Path -> Bool
$c>= :: Path -> Path -> Bool
> :: Path -> Path -> Bool
$c> :: Path -> Path -> Bool
<= :: Path -> Path -> Bool
$c<= :: Path -> Path -> Bool
< :: Path -> Path -> Bool
$c< :: Path -> Path -> Bool
compare :: Path -> Path -> Ordering
$ccompare :: Path -> Path -> Ordering
Ord) via [PathPart]
instance Show Path where
show :: Path -> String
show = Text -> String
T.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path -> Text
renderPath
instance ToJSON Path where
toJSON :: Path -> Value
toJSON = forall a. ToJSON a => a -> Value
toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path -> Text
renderPath
renderPath :: Path -> T.Text
renderPath :: Path -> Text
renderPath = (Text
pathSeparator forall a. Semigroup a => a -> a -> a
<>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> Text
T.intercalate Text
pathSeparator forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PathPart -> Text
renderPathPart forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path -> [PathPart]
unPath