{-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving, FlexibleInstances, FlexibleContexts #-}
module Web.Route.Invertible.Path
( PathString
, normalizePath
, Path(..)
, pathValues
, renderPath
, urlPathBuilder
) where
import Prelude hiding (lookup)
import Control.Invertible.Monoidal
import qualified Data.ByteString.Builder as B
import qualified Data.Invertible as I
import Data.String (IsString(..))
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import qualified Network.HTTP.Types.URI as H
import Web.Route.Invertible.Parameter
import Web.Route.Invertible.Placeholder
import Web.Route.Invertible.Sequence
type PathString = T.Text
normalizePath :: [PathString] -> [PathString]
normalizePath :: [PathString] -> [PathString]
normalizePath = (PathString -> Bool) -> [PathString] -> [PathString]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (PathString -> Bool) -> PathString -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PathString -> Bool
T.null)
newtype Path a = Path { forall a. Path a -> Sequence PathString a
pathSequence :: Sequence PathString a }
deriving ((forall a b. (a <-> b) -> Path a -> Path b) -> Functor Path
forall a b. (a <-> b) -> Path a -> Path b
forall (f :: * -> *).
(forall a b. (a <-> b) -> f a -> f b) -> Functor f
$cfmap :: forall a b. (a <-> b) -> Path a -> Path b
fmap :: forall a b. (a <-> b) -> Path a -> Path b
I.Functor, Functor Path
Path ()
Functor Path =>
Path ()
-> (forall a b. Path a -> Path b -> Path (a, b)) -> Monoidal Path
forall a b. Path a -> Path b -> Path (a, b)
forall (f :: * -> *).
Functor f =>
f () -> (forall a b. f a -> f b -> f (a, b)) -> Monoidal f
$cunit :: Path ()
unit :: Path ()
$c>*< :: forall a b. Path a -> Path b -> Path (a, b)
>*< :: forall a b. Path a -> Path b -> Path (a, b)
Monoidal, Monoidal Path
Path Void
Monoidal Path =>
Path Void
-> (forall a b. Path a -> Path b -> Path (Either a b))
-> MonoidalAlt Path
forall a b. Path a -> Path b -> Path (Either a b)
forall (f :: * -> *).
Monoidal f =>
f Void
-> (forall a b. f a -> f b -> f (Either a b)) -> MonoidalAlt f
$czero :: Path Void
zero :: Path Void
$c>|< :: forall a b. Path a -> Path b -> Path (Either a b)
>|< :: forall a b. Path a -> Path b -> Path (Either a b)
MonoidalAlt, Parameterized PathString, Int -> Path a -> ShowS
[Path a] -> ShowS
Path a -> String
(Int -> Path a -> ShowS)
-> (Path a -> String) -> ([Path a] -> ShowS) -> Show (Path a)
forall a. Int -> Path a -> ShowS
forall a. [Path a] -> ShowS
forall a. Path a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Int -> Path a -> ShowS
showsPrec :: Int -> Path a -> ShowS
$cshow :: forall a. Path a -> String
show :: Path a -> String
$cshowList :: forall a. [Path a] -> ShowS
showList :: [Path a] -> ShowS
Show)
deriving instance IsString (Path ())
pathValues :: Path a -> a -> [PlaceholderValue PathString]
pathValues :: forall a. Path a -> a -> [PlaceholderValue PathString]
pathValues (Path Sequence PathString a
p) = Sequence PathString a -> a -> [PlaceholderValue PathString]
forall s a. Sequence s a -> a -> [PlaceholderValue s]
sequenceValues Sequence PathString a
p
renderPath :: Path a -> a -> [PathString]
renderPath :: forall a. Path a -> a -> [PathString]
renderPath (Path Sequence PathString a
p) = Sequence PathString a -> a -> [PathString]
forall s a. Sequence s a -> a -> [s]
renderSequence Sequence PathString a
p
urlPathBuilder :: Path a -> a -> B.Builder
urlPathBuilder :: forall a. Path a -> a -> Builder
urlPathBuilder Path a
p a
a = (PathString -> Builder) -> [PathString] -> Builder
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap PathString -> Builder
es ([PathString] -> Builder) -> [PathString] -> Builder
forall a b. (a -> b) -> a -> b
$ Path a -> a -> [PathString]
forall a. Path a -> a -> [PathString]
renderPath Path a
p a
a where
es :: PathString -> Builder
es PathString
s = Char -> Builder
B.char7 Char
'/' Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Bool -> ByteString -> Builder
H.urlEncodeBuilder Bool
False (PathString -> ByteString
TE.encodeUtf8 PathString
s)