module Network.URI.Template.Internal.Expression
( Expression (..)
, expressionP
, expressionPretty
, expandExpression
) where
import Prelude
import Data.Map.Strict (Map)
import Data.Text (Text)
import Data.Text qualified as T
import Network.URI.Template.Internal.Operator
import Network.URI.Template.Internal.Parse
import Network.URI.Template.Internal.Pretty
import Network.URI.Template.Internal.VarSpec
import Network.URI.Template.VarName
import Network.URI.Template.VarValue
data Expression = Expression
{ Expression -> Maybe Operator
operator :: Maybe Operator
, Expression -> [VarSpec]
variableList :: [VarSpec]
}
deriving stock (Expression -> Expression -> Bool
(Expression -> Expression -> Bool)
-> (Expression -> Expression -> Bool) -> Eq Expression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Expression -> Expression -> Bool
== :: Expression -> Expression -> Bool
$c/= :: Expression -> Expression -> Bool
/= :: Expression -> Expression -> Bool
Eq, Int -> Expression -> ShowS
[Expression] -> ShowS
Expression -> String
(Int -> Expression -> ShowS)
-> (Expression -> String)
-> ([Expression] -> ShowS)
-> Show Expression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expression -> ShowS
showsPrec :: Int -> Expression -> ShowS
$cshow :: Expression -> String
show :: Expression -> String
$cshowList :: [Expression] -> ShowS
showList :: [Expression] -> ShowS
Show)
expressionP :: Parser Expression
expressionP :: Parser Expression
expressionP =
Maybe Operator -> [VarSpec] -> Expression
Expression
(Maybe Operator -> [VarSpec] -> Expression)
-> ParsecT Void Text Identity (Maybe Operator)
-> ParsecT Void Text Identity ([VarSpec] -> Expression)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'{' ParsecT Void Text Identity Char
-> ParsecT Void Text Identity (Maybe Operator)
-> ParsecT Void Text Identity (Maybe Operator)
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Operator
-> ParsecT Void Text Identity (Maybe Operator)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT Void Text Identity Operator
operatorP)
ParsecT Void Text Identity ([VarSpec] -> Expression)
-> ParsecT Void Text Identity [VarSpec] -> Parser Expression
forall a b.
ParsecT Void Text Identity (a -> b)
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (ParsecT Void Text Identity VarSpec
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity [VarSpec]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
sepBy1 ParsecT Void Text Identity VarSpec
varSpecP (Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
',') ParsecT Void Text Identity [VarSpec]
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity [VarSpec]
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'}')
expressionPretty :: Expression -> Doc Ann
expressionPretty :: Expression -> Doc Ann
expressionPretty Expression
e = do
Ann -> Doc Ann -> Doc Ann
forall ann. ann -> Doc ann -> Doc ann
annotate Ann
AnnPunctuation Doc Ann
"{"
Doc Ann -> Doc Ann -> Doc Ann
forall a. Semigroup a => a -> a -> a
<> Doc Ann -> (Operator -> Doc Ann) -> Maybe Operator -> Doc Ann
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Doc Ann
forall a. Monoid a => a
mempty (Ann -> Doc Ann -> Doc Ann
forall ann. ann -> Doc ann -> Doc ann
annotate Ann
AnnOperator (Doc Ann -> Doc Ann)
-> (Operator -> Doc Ann) -> Operator -> Doc Ann
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Operator -> Doc Ann
forall ann. Operator -> Doc ann
operatorPretty) Expression
e.operator
Doc Ann -> Doc Ann -> Doc Ann
forall a. Semigroup a => a -> a -> a
<> [Doc Ann] -> Doc Ann
forall ann. [Doc ann] -> Doc ann
hcat (Doc Ann -> [Doc Ann] -> [Doc Ann]
forall ann. Doc ann -> [Doc ann] -> [Doc ann]
punctuate Doc Ann
"," ([Doc Ann] -> [Doc Ann]) -> [Doc Ann] -> [Doc Ann]
forall a b. (a -> b) -> a -> b
$ (VarSpec -> Doc Ann) -> [VarSpec] -> [Doc Ann]
forall a b. (a -> b) -> [a] -> [b]
map VarSpec -> Doc Ann
varSpecPretty Expression
e.variableList)
Doc Ann -> Doc Ann -> Doc Ann
forall a. Semigroup a => a -> a -> a
<> Ann -> Doc Ann -> Doc Ann
forall ann. ann -> Doc ann -> Doc ann
annotate Ann
AnnPunctuation Doc Ann
"}"
expandExpression :: Map VarName VarValue -> Expression -> Text
expandExpression :: Map VarName VarValue -> Expression -> Text
expandExpression Map VarName VarValue
env Expression
e =
Text
prefix Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate OperatorActions
oa.listIntercalate [Text]
vars
where
oa :: OperatorActions
oa = OperatorActions
-> (Operator -> OperatorActions)
-> Maybe Operator
-> OperatorActions
forall b a. b -> (a -> b) -> Maybe a -> b
maybe OperatorActions
nullOperatorActions Operator -> OperatorActions
operatorActions Expression
e.operator
prefix :: Text
prefix
| [Text] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text]
vars = Text
""
| Bool
otherwise = OperatorActions
oa.listPrefix
vars :: [Text]
vars = (VarSpec -> [Text]) -> [VarSpec] -> [Text]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Map VarName VarValue -> OperatorActions -> VarSpec -> [Text]
expandVarSpec Map VarName VarValue
env OperatorActions
oa) Expression
e.variableList